2021-02-12 12:04:21 +01:00
|
|
|
program QMCChem_dataset_test
|
2021-02-23 08:28:09 +01:00
|
|
|
use Sherman_Morrison
|
|
|
|
use Helpers
|
2021-02-12 12:04:21 +01:00
|
|
|
implicit none
|
|
|
|
|
2021-02-12 17:48:49 +01:00
|
|
|
integer :: i, j, col !! Iterators
|
2021-02-12 12:04:21 +01:00
|
|
|
integer :: cycle_id, dim, n_updates
|
|
|
|
integer(c_int), dimension(:), allocatable :: Updates_index
|
2021-03-12 12:38:50 +01:00
|
|
|
real(c_double), dimension(:,:), allocatable :: Updates, U
|
2021-02-23 08:28:09 +01:00
|
|
|
real(c_double), dimension(:,:), allocatable :: S, S_inv, S_inv_t
|
2021-02-12 12:04:21 +01:00
|
|
|
|
2021-04-06 16:17:42 +02:00
|
|
|
call Read_dataset("update_cycle_13.dat", &
|
2021-02-12 19:31:31 +01:00
|
|
|
cycle_id, &
|
|
|
|
dim, &
|
|
|
|
n_updates, &
|
|
|
|
S, &
|
|
|
|
S_inv, &
|
|
|
|
Updates_index, &
|
|
|
|
Updates)
|
2021-03-12 12:38:50 +01:00
|
|
|
allocate(S_inv_t(dim,dim), U(dim,n_updates))
|
2021-02-23 08:28:09 +01:00
|
|
|
|
2021-02-12 17:48:49 +01:00
|
|
|
!! Write current S and S_inv to file for check in Octave
|
|
|
|
open(unit = 2000, file = "Slater_old.dat")
|
2021-02-18 19:43:20 +01:00
|
|
|
open(unit = 3000, file = "Slater_old_inv.dat")
|
2021-02-12 17:48:49 +01:00
|
|
|
do i=1,dim
|
|
|
|
do j=1,dim
|
|
|
|
write(2000,"(E23.15, 1X)", advance="no") S(i,j)
|
2021-02-22 09:50:42 +01:00
|
|
|
write(3000,"(E23.15, 1X)", advance="no") S_inv(i,j)
|
2021-02-12 17:48:49 +01:00
|
|
|
end do
|
|
|
|
write(2000,*)
|
|
|
|
write(3000,*)
|
|
|
|
end do
|
|
|
|
close(2000)
|
|
|
|
close(3000)
|
|
|
|
|
2021-06-15 11:53:04 +02:00
|
|
|
! !! 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)
|
2021-02-12 17:48:49 +01:00
|
|
|
|
2021-03-12 12:38:50 +01:00
|
|
|
!! Update S & transform replacement updates 'Updates'
|
|
|
|
!! into additive updates 'U' to compute the inverse
|
2021-02-12 17:48:49 +01:00
|
|
|
do j=1,n_updates
|
|
|
|
do i=1,dim
|
|
|
|
col = Updates_index(j)
|
2021-03-12 12:38:50 +01:00
|
|
|
U(i,j) = Updates(i,j) - S(i,col)
|
|
|
|
S(i,col) = Updates(i,j)
|
2021-02-12 17:48:49 +01:00
|
|
|
end do
|
|
|
|
end do
|
|
|
|
|
2021-06-15 11:53:04 +02:00
|
|
|
!! 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") U(i,j)
|
|
|
|
end do
|
|
|
|
write(2000,*)
|
|
|
|
end do
|
|
|
|
close(2000)
|
|
|
|
|
2021-02-22 09:50:42 +01:00
|
|
|
!! Update S_inv
|
2021-02-24 18:41:48 +01:00
|
|
|
!! S_inv needs to be transposed first before it
|
|
|
|
!! goes to MaponiA3
|
|
|
|
call Transpose(S_inv, S_inv_t, dim)
|
2021-04-20 16:08:09 +02:00
|
|
|
! call MaponiA3S(S_inv_t, dim, n_updates, U, Updates_index)
|
|
|
|
call SM2(S_inv_t, dim, n_updates, U, Updates_index)
|
2021-03-12 12:38:50 +01:00
|
|
|
!! S_inv_t needs to be transposed back before it
|
|
|
|
!! can be multiplied with S to test unity
|
2021-02-23 08:28:09 +01:00
|
|
|
call Transpose(S_inv_t, S_inv, dim)
|
2021-02-18 19:43:20 +01:00
|
|
|
|
2021-02-12 17:48:49 +01:00
|
|
|
!! Write new S and S_inv to file for check in Octave
|
2021-02-18 19:43:20 +01:00
|
|
|
open(unit = 4000, file = "Slater.dat")
|
|
|
|
open(unit = 5000, file = "Slater_inv.dat")
|
2021-02-12 17:48:49 +01:00
|
|
|
do i=1,dim
|
|
|
|
do j=1,dim
|
2021-02-18 19:43:20 +01:00
|
|
|
write(4000,"(E23.15, 1X)", advance="no") S(i,j)
|
|
|
|
write(5000,"(E23.15, 1X)", advance="no") S_inv(i,j)
|
2021-02-12 17:48:49 +01:00
|
|
|
end do
|
2021-02-18 19:43:20 +01:00
|
|
|
write(4000,*)
|
|
|
|
write(5000,*)
|
2021-02-12 17:48:49 +01:00
|
|
|
end do
|
2021-02-18 19:43:20 +01:00
|
|
|
close(4000)
|
|
|
|
close(5000)
|
2021-02-12 12:04:21 +01:00
|
|
|
|
2021-03-12 16:18:03 +01:00
|
|
|
deallocate(S, S_inv, S_inv_t, Updates, U, Updates_index)
|
2021-02-12 12:04:21 +01:00
|
|
|
end program
|