Sherman-Morrison/QMCChem_dataset_test.f90
François Coppens b4787e6803 Test infrastructure for hdf5 datasets and python hdf5 datasert conversion tool.
Made small corrections to compensate for changes made after branching-off from test_dataset.

Everything compilers
Everything works except for the HDF5 dataset test program that gives an I/O error.
2021-02-22 15:44:41 +01:00

73 lines
2.1 KiB
Fortran

program QMCChem_dataset_test
use Sherman_Morrison, only : MaponiA3
use Utils, only : Read_dataset
use, intrinsic :: iso_c_binding, only : c_int, c_double
implicit none
integer :: i, j, col !! Iterators
integer :: cycle_id, dim, n_updates
integer(c_int), dimension(:), allocatable :: Updates_index
real(c_double), dimension(:,:), allocatable :: Updates
real(c_double), dimension(:,:), allocatable :: S, S_inv, S_inv_trans
call Read_dataset("dataset.dat", &
cycle_id, &
dim, &
n_updates, &
S, &
S_inv, &
Updates_index, &
Updates)
!! Write current S and S_inv to file for check in Octave
open(unit = 2000, file = "Slater_old.dat")
open(unit = 3000, file = "Slater_old_inv.dat")
do i=1,dim
do j=1,dim
write(2000,"(E23.15, 1X)", advance="no") S(i,j)
write(3000,"(E23.15, 1X)", advance="no") S_inv(i,j)
end do
write(2000,*)
write(3000,*)
end do
close(2000)
close(3000)
!! Write Updates to file to check
open(unit = 2000, file = "Updates.dat")
do i=1,dim
do j=1,n_updates
write(2000,"(E23.15, 1X)", advance="no") Updates(i,j)
end do
write(2000,*)
end do
close(2000)
!! Update S
do j=1,n_updates
do i=1,dim
col = Updates_index(j)
S(i,col) = S(i,col) + Updates(i,j)
end do
end do
!! Update S_inv
call MaponiA3(S_inv, dim, n_updates, Updates, Updates_index)
!! Write new S and S_inv to file for check in Octave
open(unit = 4000, file = "Slater.dat")
open(unit = 5000, file = "Slater_inv.dat")
do i=1,dim
do j=1,dim
write(4000,"(E23.15, 1X)", advance="no") S(i,j)
write(5000,"(E23.15, 1X)", advance="no") S_inv(i,j)
end do
write(4000,*)
write(5000,*)
end do
close(4000)
close(5000)
deallocate(S, S_inv, Updates, Updates_index)
end program