! This file is copied and modified from QUANTUM ESPRESSO ! Kun Cao, Henry Lambert, Feliciano Giustino ! Copyright (C) 2009 Quantum ESPRESSO group ! 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 psym_dmage (dvtosym) !----------------------------------------------------------------------- ! ! ... p-symmetrize the magnetization change due to an electric field. ! USE kinds, ONLY : DP USE lsda_mod, ONLY : nspin USE mp_global, ONLY : me_pool USE fft_base, ONLY : dfftp, cgather_sym ! IMPLICIT NONE ! COMPLEX(DP) :: dvtosym (dfftp%nnr, nspin, 3) ! the potential to symmetrize !-local variable ! #if defined (__MPI) ! INTEGER :: i, is, iper, npp0 COMPLEX(DP), ALLOCATABLE :: ddvtosym (:,:,:) ! the potential to symm CALL start_clock ('psym_dmage') ALLOCATE (ddvtosym ( dfftp%nr1x * dfftp%nr2x * dfftp%nr3x, nspin, 3)) npp0 = 1 DO i = 1, me_pool npp0 = npp0 + dfftp%npp (i) * dfftp%nnp ENDDO DO iper = 1, 3 DO is = 1, nspin CALL cgather_sym (dvtosym (:, is, iper), ddvtosym (:, is, iper) ) ENDDO ENDDO CALL sym_dmage (ddvtosym) DO iper = 1, 3 DO is = 1, nspin CALL zcopy (dfftp%npp (me_pool+1) * dfftp%nnp, ddvtosym (npp0, is, iper), & 1, dvtosym (1, is, iper), 1) ENDDO ENDDO DEALLOCATE (ddvtosym) CALL stop_clock ('psym_dmage') #endif RETURN END SUBROUTINE psym_dmage