exciting-0.9.150
[exciting.git] / src / rdmdedc.f90
blobcae6ae0ded0eab99ca71f5207d84010a66a4175c
2 ! Copyright (C) 2007 J. K. Dewhurst, S. Sharma and E. K. U. Gross.
3 ! This file is distributed under the terms of the GNU General Public License.
4 ! See the file COPYING for license details.
6 subroutine rdmdedc(ik,dedc)
7 ! calculate the derivative of total energy w.r.t. evecsv
8 use modmain
9 implicit none
10 ! arguments
11 integer, intent(in) :: ik
12 complex(8), intent(out) :: dedc(nstsv,nstsv)
13 ! local variables
14 integer ist
15 ! allocatable arrays
16 complex(8), allocatable :: evecsv(:,:)
17 complex(8), allocatable :: c(:,:)
18 ! allocate local arrays
19 allocate(evecsv(nstsv,nstsv))
20 allocate(c(nstsv,nstsv))
21 ! get the eigenvectors from file
22 call getevecsv(vkl(1,ik),evecsv)
23 ! kinetic and Coulomb potential contribution
24 call zgemm('N','N',nstsv,nstsv,nstsv,zone,evecsv,nstsv,vclmat(1,1,ik),nstsv, &
25 zzero,c,nstsv)
26 do ist=1,nstsv
27 dedc(:,ist)=occsv(ist,ik)*(dkdc(:,ist,ik)+c(:,ist))
28 end do
29 ! exchange-correlation contribution
30 call rdmdexcdc(ik,evecsv,dedc)
31 deallocate(evecsv,c)
32 return
33 end subroutine