- Updates to data-file generated by CP to make it compatible with PW.

CP can now restart from PW , and PW (at gamma) can restart from CP.
  In CP the following control keyword should be specified:
    disk_io = 'high'
  to save the charge density
  In PW the following control keyword should be specified:
    restart_mode='restart',
    wf_collect = .true.
  to save wfc

- an example will follow


git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@3270 c92efa57-630b-4861-b058-cf58834340f0
This commit is contained in:
cavazzon 2006-07-11 16:32:39 +00:00
parent b3ec34e0b0
commit e220e33bd3
4 changed files with 156 additions and 40 deletions

View File

@ -562,6 +562,9 @@ MODULE cp_restart
!
! ... G+K vectors
!
CALL iotk_write_dat( iunpun, "NUMBER_OF_GK-VECTORS", ngwt )
!
!
filename = TRIM( wfc_filename( ".", 'gkvectors', ik ) )
!
CALL iotk_link( iunpun, "gkvectors", &
@ -571,6 +574,9 @@ MODULE cp_restart
!
END IF
!
CALL write_gk( iunout, ik, mill, filename )
!
!
DO ispin = 1, nspin
!
ik_eff = ik + ( ispin - 1 ) * nk
@ -587,7 +593,7 @@ MODULE cp_restart
!
END IF
!
CALL iotk_link( iunpun, "wfc", &
CALL iotk_link( iunpun, "WFC" // TRIM( iotk_index (ispin) ), &
filename, CREATE = .FALSE., BINARY = .TRUE. )
!
IF ( nspin == 1 ) THEN
@ -1825,4 +1831,86 @@ MODULE cp_restart
!
END SUBROUTINE read_ions
!
!
!
SUBROUTINE write_gk( iun, ik, mill, filename )
!
USE gvecw, ONLY : ngw, ngwt
USE reciprocal_vectors, ONLY : ig_l2g, mill_l
USE mp, ONLY : mp_sum
USE mp_global, ONLY : intra_image_comm
USE io_global, ONLY : ionode
!
IMPLICIT NONE
!
INTEGER, INTENT(IN) :: iun, ik
INTEGER, INTENT(IN) :: mill(:,:)
CHARACTER(LEN=256), INTENT(IN) :: filename
!
INTEGER, ALLOCATABLE :: igwk(:)
INTEGER, ALLOCATABLE :: itmp1(:)
INTEGER :: npwx_g, npw_g, ig, ngg
npwx_g = ngwt
npw_g = ngwt
ALLOCATE( igwk( npwx_g ) )
!
igwk = 0
!
ALLOCATE( itmp1( npw_g ) )
!
itmp1 = 0
!
!
DO ig = 1, ngw
!
itmp1( ig_l2g( ig ) ) = ig_l2g( ig )
!
END DO
!
CALL mp_sum( itmp1, intra_image_comm )
!
ngg = 0
!
DO ig = 1, npw_g
!
IF ( itmp1(ig) == ig ) THEN
!
ngg = ngg + 1
!
igwk( ngg ) = ig
!
END IF
!
END DO
DEALLOCATE( itmp1 )
!
IF ( ionode ) THEN
!
CALL iotk_open_write( iun, FILE = TRIM( filename ), BINARY = .TRUE. )
!
CALL iotk_write_begin( iun,"K-POINT" // iotk_index( ik ), attr )
!
CALL iotk_write_attr( attr, "NUMBER_OF_GK-VECTORS", npw_g, FIRST = .TRUE. )
CALL iotk_write_empty( iun, "INFO", ATTR = attr )
!
CALL iotk_write_dat( iun, "INDEX", igwk( 1:npw_g ) )
CALL iotk_write_dat( iun, "GRID", mill( 1:3, igwk( 1:npw_g ) ), COLUMNS = 3 )
!
CALL iotk_write_end( iun, "K-POINT" // iotk_index( ik ) )
!
CALL iotk_close_write( iun )
!
END IF
!
DEALLOCATE( igwk )
RETURN
END SUBROUTINE
!
!
!
END MODULE cp_restart

View File

@ -165,6 +165,7 @@
! ... This subroutine writes empty states to unit emptyunit
USE xml_io_base
USE mp_global, ONLY: me_image, nproc_image, intra_image_comm
USE mp_wave, ONLY: mergewf
USE mp, ONLY: mp_sum

View File

@ -225,7 +225,7 @@ CONTAINS
! ... bring wave functions onto KS states
CALL crot( 1, c0(:,:,1), cdesc, lambda, eig(:,1) )
CALL crot( c0(:,:,1), cdesc%ngwl, cdesc%nbl( 1 ), lambda, SIZE(lambda,1), eig(:,1) )
call adjef_s(eig(1,1),fi(1,1),efermi,nel, cdesc%nbl( 1 ),temp_elec,sume)
call entropy_s(fi(1,1),temp_elec,cdesc%nbl( 1 ),edft%ent)
@ -270,7 +270,7 @@ CONTAINS
CALL dforce_all( c0(:,:,1), fi(:,1), cgrad(:,:,1), vpot(:,1), vkb, bec, nupdwn(1), iupdwn(1) )
CALL proj( 1, cgrad(:,:,1), cdesc, c0(:,:,1), cdesc, lambda )
CALL crot( 1, c0(:,:,1), cdesc, lambda, eig(:,1) )
CALL crot( c0(:,:,1), cdesc%ngwl, cdesc%nbl( 1 ), lambda, SIZE(lambda,1), eig(:,1) )
call adjef_s(eig(1,1),fi(1,1),efermi,nel, cdesc%nbl( 1 ),temp_elec,sume)
call entropy_s(fi(1,1),temp_elec,cdesc%nbl(1),edft%ent)

View File

@ -198,7 +198,7 @@
!=----------------------------------------------------------------------------=!
SUBROUTINE crot_gamma ( ispin, c0, cdesc, lambda, eig )
SUBROUTINE crot_gamma ( c0, ngwl, nx, lambda, nrl, eig )
! this routine rotates the wave functions to the Kohn-Sham base
! it works with a block-like distributed matrix
@ -226,69 +226,95 @@
IMPLICIT NONE
! ... declare subroutine arguments
INTEGER, INTENT(IN) :: ngwl, nx, nrl
COMPLEX(DP), INTENT(INOUT) :: c0(:,:)
TYPE (wave_descriptor), INTENT(IN) :: cdesc
INTEGER, INTENT(IN) :: ispin
REAL(DP) :: lambda(:,:)
REAL(DP) :: eig(:)
! ... declare other variables
INTEGER :: nx, ngw, nrl
COMPLEX(DP), ALLOCATABLE :: c0rot(:,:)
REAL(DP), ALLOCATABLE :: uu(:,:), vv(:,:)
REAL(DP), ALLOCATABLE :: uu(:,:), vv(:,:), ap(:)
INTEGER :: i, j, k, ip
INTEGER :: jl, nrl_ip
! ... end of declarations
! ----------------------------------------------
nx = cdesc%nbl( ispin )
IF( nx < 1 ) THEN
RETURN
END IF
ngw = cdesc%ngwl
nrl = SIZE(lambda, 1)
ALLOCATE(uu(nrl,nx))
ALLOCATE(vv(nrl,nx))
ALLOCATE(c0rot(ngw,nx))
ALLOCATE( vv( nrl, nx ) )
ALLOCATE( c0rot( ngwl, nx ) )
c0rot = 0.0d0
uu = lambda
CALL pdspev_drv( 'V', uu, nrl, eig, vv, nrl, nrl, nx, nproc_image, me_image)
IF( nrl /= nx ) THEN
DEALLOCATE(uu)
! Distributed lambda
DO ip = 1, nproc_image
ALLOCATE( uu( nrl, nx ) )
nrl_ip = nx/nproc_image
IF((ip-1).LT.mod(nx,nproc_image)) THEN
nrl_ip = nrl_ip + 1
END IF
uu = lambda
ALLOCATE(uu(nrl_ip,nx))
IF(me_image.EQ.(ip-1)) THEN
uu = vv
END IF
CALL mp_bcast(uu, (ip-1), intra_image_comm)
CALL pdspev_drv( 'V', uu, nrl, eig, vv, nrl, nrl, nx, nproc_image, me_image)
j = ip
DO jl = 1, nrl_ip
DO i = 1, nx
CALL DAXPY(2*ngw,uu(jl,i),c0(1,j),1,c0rot(1,i),1)
DEALLOCATE(uu)
DO ip = 1, nproc_image
nrl_ip = nx/nproc_image
IF((ip-1).LT.mod(nx,nproc_image)) THEN
nrl_ip = nrl_ip + 1
END IF
ALLOCATE(uu(nrl_ip,nx))
IF(me_image.EQ.(ip-1)) THEN
uu = vv
END IF
CALL mp_bcast(uu, (ip-1), intra_image_comm)
j = ip
DO jl = 1, nrl_ip
DO i = 1, nx
CALL DAXPY(2*ngwl,uu(jl,i),c0(1,j),1,c0rot(1,i),1)
END DO
j = j + nproc_image
END DO
DEALLOCATE(uu)
END DO
ELSE
! NON distributed lambda
ALLOCATE( ap( nx * ( nx + 1 ) / 2 ) )
K = 0
DO J = 1, nx
DO I = J, nx
K = K + 1
ap( k ) = lambda( i, j )
END DO
END DO
j = j + nproc_image
END DO
DEALLOCATE(uu)
END DO
CALL dspev_drv( 'V', 'L', nx, ap, eig, vv, nx )
DEALLOCATE( ap )
DO j = 1, nrl
DO i = 1, nx
CALL DAXPY( 2*ngwl, vv(j,i), c0(1,j), 1, c0rot(1,i), 1 )
END DO
END DO
END IF
c0(:,:) = c0rot(:,:)
DEALLOCATE(vv)
DEALLOCATE(c0rot)
DEALLOCATE( vv )
DEALLOCATE( c0rot )
RETURN
END SUBROUTINE crot_gamma
@ -503,8 +529,9 @@
SUBROUTINE kohn_sham(ispin, c, cdesc, eforces, nupdwn, nupdwnl )
!
! ... declare modules
USE kinds
USE wave_constrains, ONLY: update_lambda
USE wave_types, ONLY: wave_descriptor
@ -542,7 +569,7 @@
DO ib = 1, nb_g
CALL update_lambda( ib, gam, c(:,:), cdesc, eforces(:,ib) )
END DO
CALL crot( ispin, c(:,:), cdesc, gam, eig )
CALL crot( c(:,:), cdesc%ngwl, nupdwn(ispin), gam, nupdwnl(ispin), eig )
DEALLOCATE( gam, eig )