4
1
mirror of https://github.com/pfloos/quack synced 2024-09-27 03:51:04 +02:00
quack/src/AOtoMO/AOtoMO.f90

32 lines
805 B
Fortran
Raw Normal View History

subroutine AOtoMO(nBas, nOrb, C, M_AOs, M_MOs)
2019-03-19 10:13:33 +01:00
! Perform AO to MO transformation of a matrix M_AOs for given coefficients c
! M_MOs = C.T M_AOs C
2019-03-19 10:13:33 +01:00
implicit none
integer, intent(in) :: nBas, nOrb
double precision, intent(in) :: C(nBas,nOrb)
double precision, intent(in) :: M_AOs(nBas,nBas)
2019-03-19 10:13:33 +01:00
double precision, intent(out) :: M_MOs(nOrb,nOrb)
2019-03-19 10:13:33 +01:00
double precision, allocatable :: AC(:,:)
2023-11-10 17:22:51 +01:00
allocate(AC(nBas,nOrb))
2023-11-10 17:22:51 +01:00
2024-08-28 18:39:51 +02:00
!AC = matmul(M_AOs, C)
!M_MOs = matmul(transpose(C), AC)
call dgemm("N", "N", nBas, nOrb, nBas, 1.d0, &
M_AOs(1,1), nBas, C(1,1), nBas, &
0.d0, AC(1,1), nBas)
2024-08-28 18:39:51 +02:00
call dgemm("T", "N", nOrb, nOrb, nBas, 1.d0, &
C(1,1), nBas, AC(1,1), nBas, &
0.d0, M_MOs(1,1), nOrb)
2024-08-28 18:39:51 +02:00
deallocate(AC)
2019-03-19 10:13:33 +01:00
end subroutine