1!
2! Copyright (C) 2001-2019 Quantum ESPRESSO group
3! This file is distributed under the terms of the
4! GNU General Public License. See the file `License'
5! in the root directory of the present distribution,
6! or http://www.gnu.org/copyleft/gpl.txt .
7!
8!---------------------------------------------------------------------------
9MODULE lr_variables
10  !--------------------------------------------------------------------------
11  ! ... sets the dimensions of the variables required in the
12  ! ... Lanczos linear-response calculation
13  !--------------------------------------------------------------------------
14  !
15  USE kinds,                ONLY : dp
16  USE control_flags,        ONLY : gamma_only
17  !
18  IMPLICIT NONE
19  !
20  ! Parameters
21  !
22  INTEGER, PARAMETER:: nbrx = 14   ! max number of beta functions
23  INTEGER :: iund0psi   = 20       ! unit for writing/reding of d0psi
24  INTEGER :: iundvpsi   = 200
25  INTEGER :: iunrestart = 22
26  INTEGER :: nwordd0psi, nwordrestart, n_ipol
27  CHARACTER (len=10), PARAMETER :: code1 = 'turboTDDFT', code2 = 'turboEELS'
28  INTEGER :: size_evc
29  CHARACTER (len=24) :: bgz_suffix
30  !
31  LOGICAL :: lr_exx
32  REAL(kind=dp) :: scissor
33  !
34  !------------------------------------------------------------------------!
35  ! Variables for EELS
36  !------------------------------------------------------------------------!
37  !
38  LOGICAL :: eels=.false.      ! If .true. then EELS calculation is activated
39  REAL(kind=dp) :: q1,q2,q3    ! Components of the q-vector in units of 2*pi/a
40                               ! in Cartesian coordinates
41  CHARACTER(len=30) :: approximation ! Level of approximation in TDDFPT
42  CHARACTER(LEN=256) :: tmp_dir_lr   ! Name of a temporary directory
43  CHARACTER(LEN=256) :: calculator   ! 'lanczos' or 'sternheimer'
44  !
45  ! sternheimer-eels
46  !
47  INTEGER :: nfs, & !number of frequencies for Sternheimer
48             start_freq, &
49             last_freq
50  REAL(kind=dp), ALLOCATABLE :: fiu(:), fru(:) ! frequencies for Sternheimer
51  COMPLEX(kind=dp) :: current_w ! current frequency
52  COMPLEX(DP), ALLOCATABLE :: chirr(:), &  ! charge-charge \chi
53                              chirz(:), &  ! charge-mag_z \chi
54                              chizr(:), &  ! mag_z-charge \chi
55                              chizz(:), &  ! mag_z-mag_z \chi
56                              epsm1(:)     ! epsm1
57  INTEGER :: lr1dwf
58  LOGICAL, ALLOCATABLE :: comp_f(:)
59  REAL(kind=dp) :: deltaf
60  INTEGER :: iudwf = 24
61  INTEGER :: iudrho = 23
62  INTEGER :: iu1dwf = 25
63  INTEGER :: lrdrho
64  REAL(kind=dp) :: increment
65  INTEGER :: units
66  REAL(kind=dp) :: end
67  !
68  !------------------------------------------------------------------------!
69  !
70  REAL(kind=dp), ALLOCATABLE    :: becp_1(:,:), becp1_virt(:,:)
71  COMPLEX(kind=dp), ALLOCATABLE :: becp1_c(:,:,:), becp1_c_virt(:,:,:)
72  ! the product of the beta-functions with the unperturbed wavefunctions
73  !
74  COMPLEX(kind=dp), ALLOCATABLE :: &
75       evc0(:,:,:),       &    ! the ground state wavefunctions (plane wave, band, k point)
76       evc0_virt(:,:,:),  &    ! unoccupied ground state wavefunctions (plane wave, band, k point)
77       sevc0(:,:,:),      &    ! S * ground state wavefunctions
78       sevc0_virt(:,:,:), &    ! S * virtual ground state wavefunctions
79       evc1_old(:,:,:,:), &    ! response wavefunctions in the pw basis (last
80                               ! index 1: q' using rotated SBR 2: p')
81       evc1(:,:,:,:),     &    !  "    "
82       evc1_new(:,:,:,:), &    !  "    "
83       sevc1(:,:,:),      &    ! S * "    "
84       sevc1_new(:,:,:),  &    ! S * "    "
85       d0psi(:,:,:,:),    &    ! for saving the original starting vectors
86       d0psi2(:,:,:,:),   &    ! for saving the original starting vectors (without P^+_c)
87       revc0(:,:,:),      &    ! ground state wavefunctions in real space
88       tg_revc0(:,:,:)         ! ground state wavefunctions in real space
89  REAL(kind=dp), ALLOCATABLE ::    &
90       rho_1(:,:)              ! response charge density in real space
91  COMPLEX(kind=dp), ALLOCATABLE :: &
92       rho_1c(:,:)             ! response charge density in real space
93  INTEGER :: nbnd_total        ! actual number of bands calculated by PWSCF (virtual+ocuppied)
94  INTEGER, ALLOCATABLE :: cube_save(:,:) !used in response charge density mode 1
95  !
96  COMPLEX(kind=dp), ALLOCATABLE :: F(:,:,:) ! The intensity of transition from valence state (first index)
97                                            ! to conduction  state (second index), for each polarization
98                                            ! direction (third index).
99  !
100  COMPLEX(kind=dp), ALLOCATABLE :: R(:,:,:) ! The oscillator strength from valence state (first index)
101                                            ! to conduction  state (second index), for each polarization
102                                            ! direction (third index).
103
104
105
106!  COMPLEX (DP), ALLOCATABLE ::      &
107!                  intq(:,:,:),      &! nhm, nhm, nat),        integral of e^iqr Q
108!                  intq_nc(:,:,:,:)   ! nhm, nhm, nat, nspin), integral of e^iqr Q in the noncollinear case
109  ! Lanczos Matrix
110  !
111  !
112  !       | alpha(:,1),  gamma(:,2),                             0|
113  !       | beta(:,2) ,  alpha(:,2), gamma(:,3)                   |
114  ! T^j = |           ,  beta(:,3) , ...                          |
115  !       |                                                       |
116  !       |                                       ..., gamma(:,j) |
117  !       |0                               beta(:,j) , alpha(:,j) |
118  !
119  ! Zeta is the \sum_valance (V^T_j * r_i ), where r_i is the density operator acting
120  ! on ground state orbitals
121  !
122  ! zeta.w_T gives the polarizability (w_T is the solution of
123  ! (\omega-L)e_1 = w_T , this is handled in a post processing program)
124  !
125  REAL(kind=dp), ALLOCATABLE :: &  ! (pol, iter)
126               alpha_store(:,:),&
127               beta_store(:,:), &
128               gamma_store(:,:)
129  COMPLEX(kind=dp), ALLOCATABLE :: zeta_store(:,:,:)  ! polarization of external field,
130                                                      ! polarization of internal field,
131                                                      ! iteration number.
132  !
133  ! The currently processed polarization direction and Lanczos iteration
134  !
135  INTEGER :: LR_iteration, LR_polarization ! polarization directions 1:x 2:y 3:z
136  !
137  REAL(kind=dp) :: norm0(3)
138  !
139  LOGICAL :: davidson = .false.
140  !
141  ! lr_input
142  !
143  LOGICAL :: restart            ! .true. if the calculation is a restart run
144  INTEGER :: restart_step       ! the amount of steps to write a restart file
145  INTEGER :: lr_verbosity       ! verbosity level for linear response routines
146  INTEGER :: test_case_no = 0   ! OBM, this dummy variable performs various tests
147  INTEGER :: lr_io_level = 1    ! Controls disk io
148  !
149  ! lr_control
150  !
151  INTEGER :: charge_response    ! variable for calculating response charge density
152  INTEGER :: itermax            ! number of Lanczos vectors to be calculated
153  INTEGER :: itermax_int        ! interpolated number of lanczos steps for Ritz vectors
154  LOGICAL :: ltammd             ! Tamm-Dancoff approximation
155  LOGICAL :: d0psi_rs           ! Calculate d0psi in the real space
156  LOGICAL :: lshift_d0psi       ! When calculate d0psi in real space, automatically
157                                ! shift the position operator r to the center of the molecule
158  LOGICAL :: pseudo_hermitian   ! If psedudo-Hermitian algorithm is used
159  LOGICAL :: no_hxc             ! If .true. no Hartree and exchange-correlation corrections will be considered.
160  LOGICAL :: project            ! If .true. projections to read virtual states will be calculated
161  !
162  ! lr_post
163  !
164  INTEGER :: plot_type          ! dumps rho as: 1=xyzd 2=xsf 3=cube
165  INTEGER :: sum_rule           ! currently supported sum rules : -2 for alpha(w->0)
166  !
167END MODULE lr_variables
168