open Subroutine

private subroutine open(this, filename, nInts)

Open an hdf5 file containing 6-index integrals @param[in] filename name of the file @param[out] nInts number of integrals stored in the file (normally only nonzeros)

Type Bound

lMat_hdf5_read_t

Arguments

Type IntentOptional Attributes Name
class(lMat_hdf5_read_t) :: this
character(len=*), intent(in) :: filename
integer(kind=hsize_t), intent(out) :: nInts

Contents

Source Code


Source Code

    subroutine open(this, filename, nInts)
        class(lMat_hdf5_read_t) :: this
        character(*), intent(in) :: filename
        integer(hsize_t), intent(out) :: nInts

        integer :: proc, i
        integer :: err
        integer(hsize_t) :: rest
        integer(hsize_t), allocatable :: counts(:)
        integer(MPIArg) :: procs_per_node, ierr
        character(*), parameter :: t_r = "lMat_hdf5_read_t%open"

        call h5open_f(err)
        call h5pcreate_f(H5P_FILE_ACCESS_F, this%plist_id, err)
        call h5pset_fapl_mpio_f(this%plist_id, mpi_comm_intra, mpiInfoNull, err)

        ! open the file
        call h5fopen_f(filename, H5F_ACC_RDONLY_F, this%file_id, err, access_prp=this%plist_id)

        call h5gopen_f(this%file_id, nm_grp, this%grp_id, err)

        ! get the number of integrals
        call read_int64_attribute(this%grp_id, nm_nInts, nInts, required=.true.)
        write(stdout, *) "Reading", nInts, "integrals"

        ! how many entries does each proc get?
        call MPI_Comm_Size(mpi_comm_intra, procs_per_node, ierr)
        allocate(counts(0:procs_per_node - 1))
        allocate(this%offsets(0:procs_per_node - 1))
        counts = nInts / int(procs_per_node, hsize_t)
        rest = mod(nInts, procs_per_node)
        if (rest > 0) counts(0:rest - 1) = counts(0:rest - 1) + 1

        this%offsets(0) = 0
        do proc = 1, procs_per_node - 1
            this%offsets(proc) = this%offsets(proc - 1) + counts(proc - 1)
        end do
        ! the last element to read on each proc
        if (iProcIndex_intra == procs_per_node - 1) then
            this%countsEnd = nInts - 1
        else
            this%countsEnd = this%offsets(iProcIndex_intra + 1) - 1
        end if

        call h5dopen_f(this%grp_id, nm_vals, this%ds_vals, err)
        call h5dopen_f(this%grp_id, nm_indices, this%ds_inds, err)

    end subroutine open