Sherman-Morrison/fMaponiA3_test_3x3_3.f90
François Coppens 225c841a88 * Fixed the 3x3 MaponiA3 C++ example. Update_index vector cannot have values that are smaller than 1 because the first colums in Fortran is stored at 1 and not 0.
* Started debugging reading from HDF5 formatted datasets. Slater_inv needs to be transposed before sent to Maponi. Algo fails at the last step. Correct Slater and Inverse fail to produce the identity matrix. Suspect that the matMul function is not working correctly eventhough it looks like it does.
2021-02-24 18:41:48 +01:00

60 lines
1.5 KiB
Fortran

program Interface_test
use Sherman_Morrison
implicit none
integer i, j !! Iterators
integer(c_int) :: Dim, N_updates
integer(c_int), dimension(:), allocatable :: Updates_index
real(c_double), dimension(:,:), allocatable :: A, S, Updates
real(c_double), dimension(:,:), allocatable :: S_inv
Dim = 3
N_updates = 3
allocate(Updates_index(Dim), A(Dim,Dim), S(Dim,Dim), Updates(Dim,Dim), S_inv(Dim,Dim))
!! Initialize A with M=3 and fill acc. to Eq. (17) from paper
A(1,1) = 1.0d0
A(1,2) = 1.0d0
A(1,3) = -1.0d0
A(2,1) = 1.0d0
A(2,2) = 1.0d0
A(2,3) = 0.0d0
A(3,1) = -1.0d0
A(3,2) = 0.0d0
A(3,3) = -1.0d0
do i=1,Dim
do j=1,Dim
write(*,"(F3.0,3X)", advance="no") A(i,j)
end do
write(*,*)
end do
write(*,*)
!! Prepare the diagonal matrix S and the update matrix Updates
do i=1,Dim
Updates_index(i) = i
do j=1,Dim
if (i == j) then
S(i,j) = A(i,j)
S_inv(i,j) = 1.0d0 / S(i,j)
else
S(i,j) = 0.0d0
S_inv(i,j) = 0.0d0
end if
Updates(i,j) = A(i,j) - S(i,j)
end do
end do
call MaponiA3(S_inv, Dim, N_updates, Updates, Updates_index)
do i=1,Dim
do j=1,Dim
write(*,"(F3.0,3X)", advance="no") S_inv(i,j)
end do
write(*,*)
end do
deallocate(Updates_index, A, S, Updates, S_inv)
end program