The Elk Code
timestep.f90
Go to the documentation of this file.
1 
2 ! Copyright (C) 2014 K. Krieger, 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.
5 
6 subroutine timestep
7 use modmain
8 use modtddft
9 use modmpi
10 use modomp
11 implicit none
12 ! local variables
13 integer ik,i,nthd
14 real(8) ca,dt,t1
15 complex(8) z1,z2
16 ! automatic arrays
17 real(8) w(nstsv)
18 ! allocatable arrays
19 real(8), allocatable :: vmt(:,:),vir(:),bmt(:,:,:),bir(:,:)
20 complex(8), allocatable :: evecsv(:,:),evectv(:,:),evecsvt(:,:)
21 complex(8), allocatable :: kmat(:,:),pmat(:,:,:)
22 complex(8), allocatable :: a(:,:),b(:,:),c(:,:)
23 if (itimes >= ntimes) then
24  write(*,*)
25  write(*,'("Error(timestep): itimes >= ntimes : ",2I8)') itimes,ntimes
26  write(*,*)
27  stop
28 end if
29 allocate(vmt(npcmtmax,natmtot),vir(ngtc))
30 if (spinpol) then
31  allocate(bmt(npcmtmax,natmtot,ndmag),bir(ngtc,ndmag))
32 else
33  allocate(bmt(1,1,1),bir(1,1))
34 end if
35 ! generate the Kohn-Sham potential and magnetic field in spherical coordinates
36 ! and multiply by the radial integration weights; also multiply the interstitial
37 ! potential with the characteristic function
38 call vblocal(vmt,vir,bmt,bir)
39 ! time step length
40 dt=times(itimes+1)-times(itimes)
41 ! zero the kinetic energy
42 engykn=0.d0
43 ! zero the total current
44 jtot(1:3)=0.d0
45 ! loop over k-points
46 call holdthd(nkpt/np_mpi,nthd)
47 !$OMP PARALLEL DEFAULT(SHARED) &
48 !$OMP PRIVATE(evecsv,evectv,evecsvt) &
49 !$OMP PRIVATE(kmat,pmat,w,a,b,c) &
50 !$OMP PRIVATE(i,t1,z1,z2) &
51 !$OMP NUM_THREADS(nthd)
52 allocate(evecsv(nstsv,nstsv),evectv(nstsv,nstsv),evecsvt(nstsv,nstsv))
53 allocate(kmat(nstsv,nstsv),pmat(nstsv,nstsv,3))
54 allocate(a(nstsv,nstsv),b(nstsv,nstsv),c(nstsv,nstsv))
55 !$OMP DO SCHEDULE(DYNAMIC)
56 do ik=1,nkpt
57 ! distribute among MPI processes
58  if (mod(ik-1,np_mpi) /= lp_mpi) cycle
59 ! get the kinetic matrix elements from file
60  call getkmat(ik,kmat)
61 ! get the momentum matrix elements from file
62  call getpmat(vkl(:,ik),pmat)
63 ! generate the Hamiltonian matrix in the ground-state second-variational basis
64  call genhmlt(ik,vmt,vir,bmt,bir,kmat,pmat,evectv)
65 ! diagonalise the Hamiltonian to get third-variational eigenvectors
66  if (spinpol.and.(.not.ncmag)) then
67 ! collinear case requires block diagonalisation
68  call eveqnzh(nstfv,nstsv,evectv,w)
69  evectv(nstfv+1:nstsv,1:nstfv)=0.d0
70  evectv(1:nstfv,nstfv+1:nstsv)=0.d0
71  i=nstfv+1
72  call eveqnzh(nstfv,nstsv,evectv(i,i),w(i))
73  else
74 ! non-collinear or spin-unpolarised: full diagonalisation
75  call eveqnzh(nstsv,nstsv,evectv,w)
76  end if
77 ! read in ground-state eigenvectors
78  call getevecsv('.OUT',ik,vkl(:,ik),evecsv)
79 ! convert third-variational eigenvectors to first-variational basis
80  call zgemm('N','N',nstsv,nstsv,nstsv,zone,evecsv,nstsv,evectv,nstsv,zzero,a, &
81  nstsv)
82 ! time propagate instantaneous eigenvectors across one time step
83  if (tdphi == 0.d0) then
84 ! real time evolution
85  do i=1,nstsv
86  t1=-w(i)*dt
87  z1=cmplx(cos(t1),sin(t1),8)
88  b(1:nstsv,i)=z1*a(1:nstsv,i)
89  end do
90  else
91 ! complex time evolution
92  z2=cmplx(sin(tdphi),cos(tdphi),8)
93  do i=1,nstsv
94  t1=-w(i)*dt
95  z1=exp(t1*z2)
96  b(1:nstsv,i)=z1*a(1:nstsv,i)
97  end do
98  end if
99 ! read in time-dependent Kohn-Sham eigenvectors (first-variational basis)
100  call getevecsv(filext,ik,vkl(:,ik),evecsvt)
101 ! apply time evolution operator
102  call zgemm('C','N',nstsv,nstsv,nstsv,zone,a,nstsv,evecsvt,nstsv,zzero,c,nstsv)
103  call zgemm('N','N',nstsv,nstsv,nstsv,zone,b,nstsv,c,nstsv,zzero,evecsvt,nstsv)
104 ! orthonormalise the eigenvectors if required
105  if (ntsorth > 0) then
106  if (mod(itimes-1,ntsorth) == 0) call unitary(nstsv,evecsvt)
107  end if
108 ! add to the kinetic energy
109  call engyknk(ik,kmat,evecsv,evecsvt)
110 ! add to the total current
111  call jtotk(ik,pmat,evecsv,evecsvt)
112 ! write the new eigenvectors to file
113  call putevecsv(filext,ik,evecsvt)
114 end do
115 !$OMP END DO
116 deallocate(evecsv,evectv,evecsvt)
117 deallocate(kmat,pmat,a,b,c)
118 !$OMP END PARALLEL
119 call freethd(nthd)
120 deallocate(vmt,vir,bmt,bir)
121 ! add the kinetic energy and total current from each process and redistribute
122 if (np_mpi > 1) then
123  call mpi_allreduce(mpi_in_place,engykn,1,mpi_double_precision,mpi_sum,mpicom,&
124  ierror)
125  call mpi_allreduce(mpi_in_place,jtot,3,mpi_double_precision,mpi_sum,mpicom, &
126  ierror)
127 end if
128 ! add the core kinetic energy
130 ! coupling constant of the external A-field (-1/c)
131 ca=-1.d0/solsc
132 ! add the diamagnetic current to total
133 jtot(1:3)=jtot(1:3)+ca*afieldt(1:3,itimes)*(chgtot-chgstot(1:3))
134 ! symmetrise the vector
135 call symvec(jtot)
136 ! total current magnitude
137 jtotm=norm2(jtot(1:3))
138 ! write the time step to file
139 if (mp_mpi) call writetimes
140 ! backup existing time-dependent Kohn-Sham eigenvectors if required
141 call tdbackup
142 ! synchronise MPI processes
143 call mpi_barrier(mpicom,ierror)
144 end subroutine
145 
subroutine getevecsv(fext, ikp, vpl, evecsv)
Definition: getevecsv.f90:7
integer npcmtmax
Definition: modmain.f90:216
character(256) filext
Definition: modmain.f90:1301
subroutine timestep
Definition: timestep.f90:7
subroutine writetimes
Definition: writetimes.f90:7
logical mp_mpi
Definition: modmpi.f90:17
integer ntsorth
Definition: modtddft.f90:105
integer ngtc
Definition: modmain.f90:392
real(8), dimension(3) jtot
Definition: modmain.f90:748
logical spinpol
Definition: modmain.f90:228
integer nkpt
Definition: modmain.f90:461
integer ntimes
Definition: modtddft.f90:42
integer ndmag
Definition: modmain.f90:238
real(8) engykn
Definition: modmain.f90:953
subroutine getpmat(vpl, pmat)
Definition: getpmat.f90:7
Definition: modomp.f90:6
complex(8), parameter zone
Definition: modmain.f90:1240
subroutine getkmat(ik, kmat)
Definition: getkmat.f90:7
subroutine eveqnzh(n, ld, a, w)
Definition: eveqnzh.f90:7
integer np_mpi
Definition: modmpi.f90:13
subroutine jtotk(ik, pmat, evecsv, evecsvt)
Definition: jtotk.f90:7
subroutine engyknk(ik, kmat, evecsv, evecsvt)
Definition: engyknk.f90:7
real(8) jtotm
Definition: modmain.f90:748
subroutine symvec(vc)
Definition: symvec.f90:7
real(8) engykncr
Definition: modmain.f90:955
real(8) solsc
Definition: modmain.f90:1253
complex(8), parameter zzero
Definition: modmain.f90:1240
real(8), dimension(:,:), allocatable vkl
Definition: modmain.f90:471
subroutine tdbackup
Definition: tdbackup.f90:7
Definition: modmpi.f90:6
real(8), dimension(:,:), allocatable afieldt
Definition: modtddft.f90:58
real(8), dimension(:), allocatable times
Definition: modtddft.f90:48
integer itimes
Definition: modtddft.f90:46
integer lp_mpi
Definition: modmpi.f90:15
subroutine freethd(nthd)
Definition: modomp.f90:106
subroutine holdthd(nloop, nthd)
Definition: modomp.f90:78
real(8) chgtot
Definition: modmain.f90:726
subroutine putevecsv(fext, ik, evecsv)
Definition: putevecsv.f90:7
subroutine genhmlt(ik, vmt, vir, bmt, bir, kmat, pmat, h)
Definition: genhmlt.f90:7
real(8), dimension(3) chgstot
Definition: modtddft.f90:84
integer natmtot
Definition: modmain.f90:40
subroutine unitary(n, a)
Definition: unitary.f90:10
logical ncmag
Definition: modmain.f90:240
real(8) tdphi
Definition: modtddft.f90:52
subroutine vblocal(vmt, vir, bmt, bir)
Definition: vblocal.f90:7
integer nstfv
Definition: modmain.f90:887
integer mpicom
Definition: modmpi.f90:11
integer ierror
Definition: modmpi.f90:19