quantum-espresso/PH/syme2.f90

83 lines
2.3 KiB
Fortran
Raw Normal View History

!
! Copyright (C) 2001 PWSCF 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 syme2 (dvsym)
!-------------------------------------------------------------------
!
! This routine symmetrizes the second order derivative of a scalar
! funtion read in input, with respect to electric field perturbations.
! The function in input has only the six independent components.
! The correspondence between the six components and the matrix elements of
! the symmetric 3x3 tensor are given by the common variables: jab; a1j; a2j
!
#include "f_defs.h"
use kinds, only : DP
use pwcom
use phcom
USE ramanm, ONLY: jab
implicit none
complex(DP) :: dvsym (nrx1, nrx2, nrx3, 6)
complex(DP), allocatable :: aux (:,:,:,:)
! the function to symmetrize
! auxiliary space
integer :: ix, jx, kx, ri, rj, rk, irot, ip, jp, lp, mp
! define a real-space point on the grid
! the rotated points
! counter on symmetries
! counter on polarizations
if (nsym.eq.1) return
allocate (aux(nrx1 , nrx2 , nrx3 , 6))
do ip = 1, 6
call ZCOPY (nrx1 * nrx2 * nrx3, dvsym (1, 1, 1, ip), &
1, aux (1, 1, 1, ip), 1)
enddo
dvsym (:,:,:,:) = (0.d0, 0.d0)
!
! symmmetrize
!
do kx = 1, nr3
do jx = 1, nr2
do ix = 1, nr1
do irot = 1, nsym
call ruotaijk(s (1, 1, irot), ftau (1, irot), ix, jx, kx, &
nr1, nr2, nr3, ri, rj, rk)
!
! ruotaijk finds the rotated of ix,jx,kx with the inverse of S
!
do ip = 1, 3
do jp = 1, ip
do lp = 1, 3
do mp = 1, 3
dvsym (ix, jx, kx, jab (ip, jp)) = &
dvsym (ix, jx, kx, jab (ip, jp)) + &
General cleanup of intrinsic functions: conversion to real => DBLE (including real part of a complex number) conversion to complex => CMPLX complex conjugate => CONJG imaginary part => AIMAG All functions are uppercase. CMPLX is preprocessed by f_defs.h and performs an explicit cast: #define CMPLX(a,b) cmplx(a,b,kind=DP) This implies that 1) f_defs.h must be included whenever a CMPLX is present, 2) CMPLX should stay in a single line, 3) DP must be defined. All occurrences of real, float, dreal, dfloat, dconjg, dimag, dcmplx removed - please do not reintroduce any of them. Tested only with ifc7 and g95 - beware unintended side effects Maybe not the best solution (explicit casts everywhere would be better) but it can be easily changed with a script if the need arises. The following code might be used to test for possible trouble: program test_intrinsic implicit none integer, parameter :: dp = selected_real_kind(14,200) real (kind=dp) :: a = 0.123456789012345_dp real (kind=dp) :: b = 0.987654321098765_dp complex (kind=dp) :: c = ( 0.123456789012345_dp, 0.987654321098765_dp) print *, ' A = ', a print *, ' DBLE(A)= ', DBLE(a) print *, ' C = ', c print *, 'CONJG(C)= ', CONJG(c) print *, 'DBLE(c),AIMAG(C) = ', DBLE(c), AIMAG(c) print *, 'CMPLX(A,B,kind=dp)= ', CMPLX( a, b, kind=dp) end program test_intrinsic Note that CMPLX and REAL without a cast yield single precision numbers on ifc7 and g95 !!! git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@2133 c92efa57-630b-4861-b058-cf58834340f0
2005-08-27 01:44:42 +08:00
DBLE (s (ip, lp, irot))* &
DBLE (s (jp, mp, irot))* &
aux (ri, rj, rk, jab(lp, mp))
enddo
enddo
enddo
enddo
enddo
enddo
enddo
enddo
do ip = 1, 6
General cleanup of intrinsic functions: conversion to real => DBLE (including real part of a complex number) conversion to complex => CMPLX complex conjugate => CONJG imaginary part => AIMAG All functions are uppercase. CMPLX is preprocessed by f_defs.h and performs an explicit cast: #define CMPLX(a,b) cmplx(a,b,kind=DP) This implies that 1) f_defs.h must be included whenever a CMPLX is present, 2) CMPLX should stay in a single line, 3) DP must be defined. All occurrences of real, float, dreal, dfloat, dconjg, dimag, dcmplx removed - please do not reintroduce any of them. Tested only with ifc7 and g95 - beware unintended side effects Maybe not the best solution (explicit casts everywhere would be better) but it can be easily changed with a script if the need arises. The following code might be used to test for possible trouble: program test_intrinsic implicit none integer, parameter :: dp = selected_real_kind(14,200) real (kind=dp) :: a = 0.123456789012345_dp real (kind=dp) :: b = 0.987654321098765_dp complex (kind=dp) :: c = ( 0.123456789012345_dp, 0.987654321098765_dp) print *, ' A = ', a print *, ' DBLE(A)= ', DBLE(a) print *, ' C = ', c print *, 'CONJG(C)= ', CONJG(c) print *, 'DBLE(c),AIMAG(C) = ', DBLE(c), AIMAG(c) print *, 'CMPLX(A,B,kind=dp)= ', CMPLX( a, b, kind=dp) end program test_intrinsic Note that CMPLX and REAL without a cast yield single precision numbers on ifc7 and g95 !!! git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@2133 c92efa57-630b-4861-b058-cf58834340f0
2005-08-27 01:44:42 +08:00
call DSCAL (2 * nrx1 * nrx2 * nrx3, 1.d0 / DBLE (nsym), &
dvsym (1, 1, 1, ip), 1)
enddo
deallocate (aux)
return
end subroutine syme2