pwdft  0.1
PW-DFT code for education
lobpcg Module Reference

Functions/Subroutines

subroutine diag_ovrp (nsub, hsub, ovlp, esub)
 
subroutine lobpcg_main (npw, kvec, evec, eval, istep)
 

Function/Subroutine Documentation

◆ diag_ovrp()

subroutine lobpcg::diag_ovrp ( integer, intent(in)  nsub,
complex(8), dimension(nsub,nsub), intent(inout)  hsub,
complex(8), dimension(nsub,nsub), intent(inout)  ovlp,
real(8), dimension(nsub), intent(out)  esub 
)

Definition at line 30 of file lobpcg.F90.

30  !
31  integer,intent(in) :: nsub
32  complex(8),intent(inout) :: hsub(nsub,nsub), ovlp(nsub,nsub)
33  real(8),intent(out) :: esub(nsub)
34  !
35  integer :: lwork, isub, nsub2, info
36  real(8) :: rwork(3*nsub-2)
37  complex(8),allocatable :: work(:)
38  !
39  lwork = -1
40  allocate(work(1))
41  call zheev('V', 'U', nsub, ovlp, nsub, esub, work, lwork, rwork, info)
42  lwork = nint(dble(work(1)))
43  deallocate(work)
44  allocate(work(lwork))
45  call zheev('V', 'U', nsub, ovlp, nsub, esub, work, lwork, rwork, info)
46  deallocate(work)
47  !
48  nsub2 = 0
49  do isub = 1, nsub
50  if(esub(isub) > 1.0d-14) then
51  nsub2 = nsub2 + 1
52  ovlp(1:nsub,nsub2) = ovlp(1:nsub,isub) / sqrt(esub(isub))
53  end if
54  end do
55  ovlp(1:nsub,nsub2+1:nsub) = 0.0d0
56  !
57  hsub(1:nsub2,1:nsub2) = matmul(conjg(transpose(ovlp(1:nsub,1:nsub2))), &
58  & matmul(hsub(1:nsub,1:nsub), ovlp(1:nsub,1:nsub2)))
59  !
60  lwork = -1
61  allocate(work(1))
62  call zheev('V', 'U', nsub2, hsub, nsub, esub, work, lwork, rwork, info)
63  lwork = nint(dble(work(1)))
64  deallocate(work)
65  allocate(work(lwork))
66  call zheev('V', 'U', nsub2, hsub, nsub, esub, work, lwork, rwork, info)
67  deallocate(work)
68  !
69  hsub(1:nsub, 1:nsub2) = matmul(ovlp(1:nsub,1:nsub2), hsub(1:nsub2,1:nsub2))
70  hsub(1:nsub, nsub2+1:nsub) = 0.0d0
71  !

Referenced by lobpcg_main().

Here is the caller graph for this function:

◆ lobpcg_main()

subroutine lobpcg::lobpcg_main ( integer, intent(in)  npw,
real(8), dimension(3), intent(in)  kvec,
complex(8), dimension(npw,nbnd), intent(inout)  evec,
real(8), dimension(nbnd), intent(out)  eval,
integer, intent(out)  istep 
)

Definition at line 75 of file lobpcg.F90.

75  !
76  use kohn_sham, only : nbnd, calculation
77  use hamiltonian, only : h_psi
78  use atm_spec, only : bvec
79  use gvec, only : g_wf
80  !
81  integer,intent(in) :: npw
82  real(8),intent(in) :: kvec(3)
83  real(8),intent(out) :: eval(nbnd)
84  complex(8),intent(inout) :: evec(npw,nbnd)
85  integer,intent(out) :: istep
86  !
87  integer :: ii, ibnd, nsub, ipw, cg_maxstep = 100
88  real(8) :: norm, maxnorm, ekin(npw), pre(npw), gv(3), ekin0, &
89  & cg_thr = 1.0d-4, esub(3*nbnd)
90  complex(8) :: wxp(npw,nbnd,3), hwxp(npw,nbnd,3), xp(npw,nbnd,2:3), &
91  & hsub(nbnd,3,3*nbnd), ovlp(3*nbnd,3*nbnd), rotmat(nbnd,3,nbnd,2:3)
92  !
93  do ipw = 1, g_wf%npw
94  gv(1:3) = matmul(bvec(1:3,1:3), dble(g_wf%mill(1:3,g_wf%map(ipw))))
95  ekin(ipw) = dot_product(gv,gv)
96  end do
97  !
98  nsub = 3 * nbnd
99  xp( 1:npw,1:nbnd,2:3) = 0.0d0
100  wxp( 1:npw,1:nbnd,1:3) = 0.0d0
101  hwxp(1:npw,1:nbnd,1:3) = 0.0d0
102  !
103  wxp(1:npw,1:nbnd,2) = evec(1:npw,1:nbnd)
104  !
105  call h_psi(kvec,wxp(1:npw,1:nbnd,2), hwxp(1:npw,1:nbnd,2))
106  !
107  do ibnd = 1, nbnd
108  esub(ibnd) = dble(dot_product(wxp(1:npw,ibnd,2), hwxp(1:npw,ibnd,2)))
109  end do
110  !
111  if(calculation=="iterative") write(*,*) "Step Residual"
112  !
113  do istep = 1, cg_maxstep
114  !
115  maxnorm = 0.0d0
116  do ibnd = 1, nbnd
117  !
118  wxp(1:npw,ibnd,1) = hwxp(1:npw,ibnd,2) - esub(ibnd) * wxp(1:npw,ibnd,2)
119  norm = sqrt(dble(dot_product(wxp(1:npw,ibnd,1), wxp(1:npw,ibnd,1))))
120  maxnorm = max(norm, maxnorm)
121  !
122  ! Preconditioning
123  !
124  ekin0 = sum(dble(conjg(wxp(1:npw,ibnd,2))*(wxp(1:npw,ibnd,2))*ekin(1:npw)))
125  pre(1:npw) = ekin(1:npw) / ekin0
126  pre(1:npw) = (27.0d0 + pre(1:npw)*(18.0d0 + pre(1:npw)*(12.0d0 * pre(1:npw)*8.0d0))) &
127  & / (27.0d0 + pre(1:npw)*(18.0d0 + pre(1:npw)*(12.0d0 + pre(1:npw)*(8.0d0 + pre(1:npw)*16.0d0))))
128  !
129  wxp(1:npw,ibnd,1) = wxp(1:npw,ibnd,1) * pre(1:npw)
130  !
131  ! Normalize
132  !
133  norm = sqrt(dble(dot_product(wxp(1:npw,ibnd,1), wxp(1:npw,ibnd,1))))
134  wxp(1:npw,ibnd,1) = wxp(1:npw,ibnd,1) / norm
135  !
136  end do
137  if(calculation == "iterative") write(*,*) " ", istep, maxnorm
138  if(maxnorm < cg_thr) exit
139  !
140  call h_psi(kvec,wxp(1:npw,1:nbnd,1), hwxp(1:npw,1:nbnd,1))
141  !
142  call zgemm("C", "N", 3*nbnd, 3*nbnd, npw, &
143  & (1.0d0,0.0d0), wxp, npw, hwxp, npw, (0.0d0,0.0d0), hsub, 3*nbnd)
144  call zgemm("C", "N", 3*nbnd, 3*nbnd, npw, &
145  & (1.0d0,0.0d0), wxp, npw, wxp, npw, (0.0d0,0.0d0), ovlp, 3*nbnd)
146  !
147  call diag_ovrp(nsub,hsub,ovlp,esub)
148  !
149  rotmat(1:nbnd,1:3,1:nbnd,2) = hsub(1:nbnd,1:3,1:nbnd)
150  rotmat(1:nbnd, 1,1:nbnd,3) = hsub(1:nbnd, 1,1:nbnd)
151  rotmat(1:nbnd, 2,1:nbnd,3) = 0.0d0
152  rotmat(1:nbnd, 3,1:nbnd,3) = hsub(1:nbnd, 3,1:nbnd)
153  !
154  call zgemm("N", "N", npw, 2*nbnd, 3*nbnd, &
155  & (1.0d0,0.0d0), wxp, npw, rotmat, 3*nbnd, (0.0d0,0.0d0), xp, npw)
156  wxp(1:npw,1:nbnd,2:3) = xp(1:npw,1:nbnd,2:3)
157  call zgemm("N", "N", npw, 2*nbnd, 3*nbnd, &
158  & (1.0d0,0.0d0), hwxp, npw, rotmat, 3*nbnd, (0.0d0,0.0d0), xp, npw)
159  hwxp(1:npw,1:nbnd,2:3) = xp(1:npw,1:nbnd,2:3)
160  !
161  do ii = 2, 3
162  do ibnd = 1, nbnd
163  norm = sqrt(dble(dot_product(wxp(1:npw,ibnd,ii), wxp(1:npw,ibnd,ii))))
164  wxp( 1:npw,ibnd,ii) = wxp(1:npw,ibnd,ii) / norm
165  hwxp(1:npw,ibnd,ii) = hwxp(1:npw,ibnd,ii) / norm
166  end do
167  end do
168  !
169  end do
170  !
171  if(istep >= cg_maxstep) then
172  write(*,*) " Not converged at kvec : ", kvec(1:3), ", norm : ", maxnorm
173  end if
174  !
175  evec(1:npw,1:nbnd) = wxp(1:npw,1:nbnd,2)
176  eval(1:nbnd) = esub(1:nbnd)
177  !

References atm_spec::bvec, kohn_sham::calculation, diag_ovrp(), gvec::g_wf, hamiltonian::h_psi(), and kohn_sham::nbnd.

Referenced by scf::kohn_sham_eq().

Here is the call graph for this function:
Here is the caller graph for this function:
kohn_sham::calculation
character(256), save calculation
Calculation mode.
Definition: kohn_sham.F90:27
hamiltonian::h_psi
subroutine h_psi(kvec, psi, hpsi)
Definition: hamiltonian.F90:30
gvec
Definition: gvec.F90:23
hamiltonian
Definition: hamiltonian.F90:23
atm_spec
Definition: atm_spec.F90:23
kohn_sham
Definition: kohn_sham.F90:23