From 300d6f536c4db811e9ad2e1104c1e2d572f0aaa0 Mon Sep 17 00:00:00 2001 From: umari Date: Fri, 21 Oct 2005 19:40:15 +0000 Subject: [PATCH] Fixed C.G., ENSEMBLE-DFT, ELECTRIC FIELD P.U. git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@2340 c92efa57-630b-4861-b058-cf58834340f0 --- CPV/cg.f90 | 16 ++++++++-------- CPV/cg_sub.f90 | 11 +++-------- CPV/cglib.f90 | 4 ++-- CPV/cplib.f90 | 3 ++- CPV/cprsub.f90 | 2 ++ 5 files changed, 17 insertions(+), 19 deletions(-) diff --git a/CPV/cg.f90 b/CPV/cg.f90 index 52eff6927..3d8bc872e 100644 --- a/CPV/cg.f90 +++ b/CPV/cg.f90 @@ -11,15 +11,15 @@ MODULE cg_module IMPLICIT NONE SAVE - logical :: tcg = .false. ! se vero fa gradiente coniugato - integer :: maxiter = 20 !numero massimo interazioni c.g. - real(8) :: etresh = 1.d-5 !soglia convergenza c.g. - real(8) :: passop =0.3d0 !passetto per gradiente coniugato + logical :: tcg = .false. ! if true do conjugate gradient minimization for electrons + integer :: maxiter = 100 ! maximum number of iterations + real(8) :: etresh = 1.d-5 !energy treshold + real(8) :: passop =0.3d0 !small step for conjugate gradient !*** !*** Conjugate Gradient !*** - real(8) esse,essenew !fattori cg + real(8) esse,essenew !factors in c.g. COMPLEX(8), ALLOCATABLE :: gi(:,:)!coniugati COMPLEX(8), ALLOCATABLE :: hi(:,:)!gradienti di ricerca COMPLEX(8), ALLOCATABLE :: c0old(:,:)!vecchie funzioni d'onda, per estrapolazione @@ -64,9 +64,9 @@ CONTAINS write (stdout,400) maxiter,etresh,passop endif 400 format (/4x,'=====================================' & - & /4x,'| GRADIENTE CONIUGATO |' & + & /4x,'| CONJUGATE GRADIENT |' & & /4x,'=====================================' & - & /4x,'| iterazioni =',i10,' |' & + & /4x,'| iterations =',i10,' |' & & /4x,'| etresh =',f10.5,' a.u. |' & & /4x,'| passop =',f10.5,' a.u. |' & & /4x,'=====================================') @@ -77,7 +77,7 @@ CONTAINS SUBROUTINE allocate_cg( ngw, nx ) IMPLICIT NONE INTEGER, INTENT(IN) :: ngw, nx - allocate(hi(ngw,nx))!poi bisogna fare che uno semplicemnte punti su cm + allocate(hi(ngw,nx)) allocate(gi(ngw,nx)) allocate(c0old(ngw,nx)) allocate( emme(nx,nx)) diff --git a/CPV/cg_sub.f90 b/CPV/cg_sub.f90 index 456cd6f6b..373b21061 100644 --- a/CPV/cg_sub.f90 +++ b/CPV/cg_sub.f90 @@ -119,7 +119,7 @@ fion2=0.d0 - open(37,file='convergenza.dat',status='unknown')!for debug and tuning purposes + !open(37,file='convergenza.dat',status='unknown')!for debug and tuning purposes if(tfirst.and.ionode) write(stdout,*) 'PERFORMING CONJUGATE GRADIENT MINIMIZATION OF EL. STATES' call prefor(eigr,betae) @@ -205,7 +205,7 @@ ene_ok=.false. end if ENERGY_CHECK - write(37,*)itercg, etotnew,pberryel!for debug and tuning purposes + !write(37,*)itercg, etotnew,pberryel!for debug and tuning purposes @@ -1064,16 +1064,13 @@ itercg=itercg+1 end do!on conjugate gradient iterations - write(6,*)'Control 1', fion(3,1), fion(3,64)!ATTENZIONE !calculates atomic forces and lambda call newd(rhor,irb,eigrb,rhovan,fion) - write(6,*)'Control 2', fion(3,1), fion(3,64)!ATTENZIONE if (.not.tens) then if (tfor .or. tprnfor) call nlfq(c0,eigr,bec,becdr,fion) else if (tfor .or. tprnfor) call nlfq(c0diag,eigr,becdiag,becdrdiag,fion) endif - write(6,*)'Control 3', fion(3,1), fion(3,64)!ATTENZIONE call prefor(eigr,betae) do i=1,n,2 @@ -1136,13 +1133,11 @@ ! bforceion adds the force term due to electronic berry phase ! only in US-case - write(6,*)'Control 4', fion(3,1), fion(3,64)!ATTENZIONE if( tefield.and.(evalue .ne. 0.d0) ) then call bforceion(fion,tfor.or.tprnfor,ipolp, qmat,bec,becdr,gqq,evalue) endif - write(6,*)'Control 3', fion(3,1), fion(3,64)!ATTENZIONE - close(37)!for debug and tuning purposes + !close(37)!for debug and tuning purposes END SUBROUTINE diff --git a/CPV/cglib.f90 b/CPV/cglib.f90 index 37d42a28c..f86540655 100644 --- a/CPV/cglib.f90 +++ b/CPV/cglib.f90 @@ -32,7 +32,7 @@ integer is, iv, jv, ia, inl, jnl, i, j real(8) qtemp(nhsavb,n) ! automatic array ! - phi = 0.0d0 + phi(1:ngw,1:n) = 0.0d0 ! if (nvb.gt.0) then qtemp = 0.0d0 @@ -148,7 +148,7 @@ real(8) bec(nhsa,n), becdiag(nhsa,n) complex(8) c0(ngw,nx), c0diag(ngw,nx) - c0diag(:,ni+istart-1) = 0.0d0 + c0diag(1:ngw,1:nx)=0.d0 do iss=1,nspin nss=nupdwn(iss) istart=iupdwn(iss) diff --git a/CPV/cplib.f90 b/CPV/cplib.f90 index 5f8837cb1..fa49c874b 100644 --- a/CPV/cplib.f90 +++ b/CPV/cplib.f90 @@ -2675,6 +2675,7 @@ use dener use io_global, only: stdout use funct, only: ismeta + use cg_module, only : tcg ! implicit none real(8) bec(nhsa,n), rhovan(nhm*(nhm+1)/2,nat,nspin) @@ -2915,7 +2916,7 @@ & ' rhoofr: rmin rmax rnegsum rsum ',rmin,rmax,rnegsum,rsum end if ! - if( nfi == 0 .or. mod(nfi, iprint) == 0 ) then + if( nfi == 0 .or. mod(nfi, iprint) == 0 .and. .not. tcg) then do iss=1,nspin rsumg(iss)=omega*DBLE(rhog(1,iss)) diff --git a/CPV/cprsub.f90 b/CPV/cprsub.f90 index a8dd7e659..02ba467c1 100644 --- a/CPV/cprsub.f90 +++ b/CPV/cprsub.f90 @@ -167,7 +167,9 @@ subroutine newnlinit ! ! non-linear core-correction ( rhocb(ig,is) ) ! + CALL core_charge_ftr( tpre ) + ! return !