!----------------------------------------------------------------------- ! Copyright (C) 2010-2015 Henry Lambert, Feliciano Giustino ! This file is distributed under the terms of the GNU General Public ! License. See the file `LICENSE' in the root directory of the ! present distribution, or http://www.gnu.org/copyleft.gpl.txt . !----------------------------------------------------------------------- SUBROUTINE green_linsys_shift_im (green, xk1, iw0, mu, iq, nwgreen) USE kinds, ONLY : DP USE ions_base, ONLY : nat, ntyp => nsp, ityp USE io_global, ONLY : stdout, ionode USE io_files, ONLY : prefix, iunigk USE check_stop, ONLY : check_stop_now USE wavefunctions_module, ONLY : evc USE constants, ONLY : degspin, pi, tpi, RYTOEV, eps8 USE cell_base, ONLY : tpiba2 USE ener, ONLY : ef USE klist, ONLY : xk, wk, nkstot USE lsda_mod, ONLY : lsda, nspin, current_spin, isk USE wvfct, ONLY : nbnd, npw, npwx, igk, g2kin, et, ecutwfc USE uspp, ONLY : okvan, vkb USE uspp_param, ONLY : upf, nhm, nh USE noncollin_module, ONLY : noncolin, npol, nspin_mag USE control_gw, ONLY : rec_code, niter_gw, nmix_gw, tr2_gw, & alpha_pv, lgamma, lgamma_gamma, convt, & nbnd_occ, alpha_mix, ldisp, rec_code_read, & where_rec, current_iq, ext_recover, & eta, tr2_green, maxter_green, prec_shift,& multishift USE nlcc_gw, ONLY : nlcc_any USE units_gw, ONLY : iuwfc, lrwfc, iuwfcna, iungreen, lrgrn USE eqv, ONLY : evq, eprectot USE qpoint, ONLY : xq, npwq, igkq, nksq, ikks, ikqs USE disp, ONLY : nqs, x_q USE freq_gw, ONLY : fpol, fiu, nfs, nfsmax, wgreen, deltaw, w0pmw USE gwsigma, ONLY : sigma_c_st, ecutsco, ecutprec USE gvect, ONLY : g, ngm USE mp, ONLY : mp_sum, mp_barrier, mp_bcast USE mp_images, ONLY : nimage, my_image_id, intra_image_comm, & me_image, nproc_image, inter_image_comm USE mp_global, ONLY : nproc_pool_file, & nproc_bgrp_file, nproc_image_file USE mp_bands, ONLY : nproc_bgrp, ntask_groups USE mp_world, ONLY : nproc, mpime USE mp_pools, ONLY : inter_pool_comm IMPLICIT NONE !should be freq blocks... !complex(DP) :: gr_A_shift(npwx, nwgreen) complex(DP), ALLOCATABLE :: gr_A_shift(:,:) complex(DP) :: gr_A(npwx, 1), rhs(npwx , 1) complex(DP) :: gr(npwx, 1), ci, cw complex(DP) :: green(sigma_c_st%ngmt, sigma_c_st%ngmt, nwgreen) complex(DP), ALLOCATABLE :: etc(:,:) real(DP) :: dirac, x, delta, support real(DP) :: k0mq(3) real(DP) :: w_ryd(nwgreen) real(DP) , allocatable :: h_diag (:,:) real(DP) :: eprec_gamma real(DP) :: thresh, anorm, averlt, dr2, sqrtpi real(DP) :: ehomo, elumo, mu real(DP) :: gam(3) real(DP) :: xk1(3) integer :: nwgreen integer :: iw, igp, iw0 integer :: iq, ik0 integer :: rec0, n1, gveccount integer, ALLOCATABLE :: niters(:) integer :: kter, & ! counter on iterations iter0, & ! starting iteration ipert, & ! counter on perturbations ibnd, & ! counter on bands iter, & ! counter on iterations lter, & ! counter on iterations of linear system ltaver, & ! average counter lintercall, & ! average number of calls to cgsolve_all ik, ikk, & ! counter on k points ikq, & ! counter on k+q points ig, & ! counter on G vectors ndim, & ! integer actual row dimension of dpsi is, & ! counter on spin polarizations nt, & ! counter on types na, & ! counter on atoms nrec, nrec1,& ! the record number for dvpsi and dpsi ios, & ! integer variable for I/O control mode ! mode index integer :: igkq_ig(npwx) integer :: igkq_tmp(npwx) integer :: counter integer :: igstart, igstop, ngpool, ngr, igs, ngvecs logical :: conv_root external cg_psi, ch_psi_all_green ALLOCATE (h_diag (npwx, 1)) ALLOCATE (etc(nbnd_occ(1), nkstot)) if(multishift) ALLOCATE(gr_A_shift(npwx, nwgreen)) ci = (0.0d0, 1.0d0) !Convert freq array generated in freqbins into rydbergs. do iw =1, nwgreen w_ryd(iw) = w0pmw(1,iw)/RYTOEV enddo call start_clock('greenlinsys') where_rec='no_recover' !This should ensure the Green's fxn has the correct -\delta for \omega