IO: Use store_dataset_h5() in store_variables_h5().
The subroutine write_variables_h5() was renamed to store_variables_h5(). Signed-off-by: Grzegorz Kowal <grzegorz@amuncode.org>
This commit is contained in:
parent
90052f4c62
commit
192ddc4d7e
@ -3879,7 +3879,7 @@ module io
|
||||
|
||||
call write_coordinates_h5(fid, status)
|
||||
|
||||
call write_variables_h5(fid, status)
|
||||
call store_variables_h5(fid, status)
|
||||
|
||||
call h5fclose_f(fid, status)
|
||||
if (status > 0) then
|
||||
@ -5398,82 +5398,84 @@ module io
|
||||
!
|
||||
!===============================================================================
|
||||
!
|
||||
! subroutine WRITE_VARIABLES_H5:
|
||||
! subroutine STORE_VARIABLES_H5:
|
||||
! -----------------------------
|
||||
!
|
||||
! Subroutine stores primitive variables in specific group.
|
||||
!
|
||||
! Arguments:
|
||||
!
|
||||
! fid - the HDF5 file identifier;
|
||||
! loc_id - the location in which store the variables;
|
||||
! status - the subroutine call status;
|
||||
!
|
||||
!===============================================================================
|
||||
!
|
||||
subroutine write_variables_h5(fid, status)
|
||||
subroutine store_variables_h5(loc_id, status)
|
||||
|
||||
use hdf5
|
||||
use blocks , only : block_data, list_data
|
||||
use blocks , only : get_dblocks
|
||||
use coordinates, only : bcells
|
||||
use equations , only : nv, pvars
|
||||
use helpers , only : print_message
|
||||
use blocks , only : block_data, list_data
|
||||
use blocks , only : get_dblocks
|
||||
use coordinates , only : bcells
|
||||
use equations , only : nv, pvars
|
||||
use helpers , only : print_message
|
||||
use iso_c_binding, only : c_loc
|
||||
|
||||
implicit none
|
||||
|
||||
integer(hid_t), intent(in) :: fid
|
||||
integer(hid_t), intent(in) :: loc_id
|
||||
integer , intent(out) :: status
|
||||
|
||||
integer(hid_t) :: gid
|
||||
integer(hid_t) :: grp_id
|
||||
integer :: n, p
|
||||
|
||||
integer(hsize_t), dimension(4) :: dims = 1
|
||||
|
||||
type(block_data), pointer :: pdata
|
||||
|
||||
integer(hsize_t), dimension(4) :: dm = 1
|
||||
real(kind=8), dimension(:,:,:,:), allocatable, target :: array
|
||||
|
||||
real(kind=8), dimension(:,:,:,:), allocatable :: array
|
||||
|
||||
character(len=*), parameter :: loc = 'IO::write_variables_h5()'
|
||||
character(len=*), parameter :: loc = 'IO::store_variables_h5()'
|
||||
|
||||
!-------------------------------------------------------------------------------
|
||||
!
|
||||
status = 0
|
||||
|
||||
call h5gcreate_f(fid, 'variables', gid, status)
|
||||
call h5gcreate_f(loc_id, 'variables', grp_id, status)
|
||||
if (status >= 0) then
|
||||
|
||||
if (get_dblocks() > 0) then
|
||||
|
||||
dm(1:NDIMS) = bcells
|
||||
dm(4) = get_dblocks()
|
||||
dims(1:NDIMS) = bcells
|
||||
dims(4) = get_dblocks()
|
||||
|
||||
allocate(array(dm(1),dm(2),dm(3),dm(4)), stat=status)
|
||||
allocate(array(dims(1),dims(2),dims(3),dims(4)), stat=status)
|
||||
if (status /= 0) then
|
||||
call print_message(loc, "Could not allocate the variables array!")
|
||||
call print_message(loc, "Could not allocate space for variables!")
|
||||
else
|
||||
do p = 1, nv
|
||||
n = 1
|
||||
n = 0
|
||||
pdata => list_data
|
||||
do while(associated(pdata))
|
||||
n = n + 1
|
||||
|
||||
array(:,:,:,n) = pdata%q(p,:,:,:)
|
||||
n = n + 1
|
||||
|
||||
pdata => pdata%next
|
||||
end do
|
||||
|
||||
call write_array(gid, trim(pvars(p)), dm, array)
|
||||
call store_dataset_h5(grp_id, trim(pvars(p)), H5T_NATIVE_DOUBLE, &
|
||||
dims, c_loc(array), status)
|
||||
end do
|
||||
|
||||
deallocate(array, stat=status)
|
||||
if (status > 0) &
|
||||
call print_message(loc, "Could not deallocate the variables array!")
|
||||
if (status /= 0) &
|
||||
call print_message(loc, "Could not deallocate the variable space!")
|
||||
end if
|
||||
|
||||
end if
|
||||
|
||||
call h5gclose_f(gid, status)
|
||||
if (status > 0) &
|
||||
call h5gclose_f(grp_id, status)
|
||||
if (status < 0) &
|
||||
call print_message(loc, "Could not close group 'variables'!")
|
||||
else
|
||||
call print_message(loc, "Could not create group 'variables'!")
|
||||
@ -5481,7 +5483,7 @@ module io
|
||||
|
||||
!-------------------------------------------------------------------------------
|
||||
!
|
||||
end subroutine write_variables_h5
|
||||
end subroutine store_variables_h5
|
||||
!
|
||||
!===============================================================================
|
||||
!
|
||||
|
Loading…
x
Reference in New Issue
Block a user