quantum-espresso/PHonon/PH/symdynph_gq.f90

180 lines
6.2 KiB
Fortran
Raw Normal View History

!
Cleanup of the symmetry initialization of the phonon code. Two main changes: The array irgq is removed. The small group of q is calculated only in one routine. The removal of the irgq array changed the list of input parameters of several routines that may be called by external applications linked with the phonon. I have tried not to break the compatibility with these codes adding a suffix _new to the routines that required a change of input parameters. The old routines are still there and can be linked as before, but have been moved to a single file. The old routines are: smallgq -> becomes a routine called set_giq that sets only gi, gimq and finds irotmq if minus_q is .true. It does not recalculate the small group of q. set_irr set_irr_nosym set irr_mode are substituted by the two routines: set_irr_new set_irr_nosym_new set_irr_mode is no more necessary. The input variables of the new routines have been reduced. These routines set u, nirr, npert and these are the only variables that are passed. All the others are passed by USE association. Moreover these routines do not recalculate any more the small group of q. set_irr_sym -> set_irr_sym_new (reduced the number of input parameters) This routine sets t, tmq. sgama_ph -> sgama_ph_new (the array sym is no more needed as input variable) symdyn_munu -> symdyn_munu_new (the array irgq is no more in input variables) symdynph_gq -> symdynph_gq_new (the array irgq is no more in input variables) random_matrix -> random_matrix_new (the array irgq is no more in input variables) dynmat0 -> dynmat0_new (call the new symdyn_munu_new) dynmatrix -> dynmatrix_new (call the new symdyn_munu_new) PAW_dusymmetrize (the array irgq has been removed from the list of input variables, but the name of this routine has not been changed) The old routines are in the file PHonon/PH/obsolete.f90. This file will disapper in the future and the new routines will substitute the old ones, so if you use these routines, you may update the argument list to the new ones or copy the routines that you need in the directory of your application (not advised) and change their names. Moreover soon the array irgq will disappear from phcom. Due to the changes in the organization of the symmetry routines in pw.x now irgq(1)=1, irgq(2)=2, irgq(3)=3, ... and it is no more necessary to use it. It can be safely removed from the routines that use it. If you think that you need it, please create a copy in your common variables. The array was set by smallgq. git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@9273 c92efa57-630b-4861-b058-cf58834340f0
2012-08-08 00:56:57 +08:00
! Copyright (C) 2001-2012 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 .
!
!-----------------------------------------------------------------------
Cleanup of the symmetry initialization of the phonon code. Two main changes: The array irgq is removed. The small group of q is calculated only in one routine. The removal of the irgq array changed the list of input parameters of several routines that may be called by external applications linked with the phonon. I have tried not to break the compatibility with these codes adding a suffix _new to the routines that required a change of input parameters. The old routines are still there and can be linked as before, but have been moved to a single file. The old routines are: smallgq -> becomes a routine called set_giq that sets only gi, gimq and finds irotmq if minus_q is .true. It does not recalculate the small group of q. set_irr set_irr_nosym set irr_mode are substituted by the two routines: set_irr_new set_irr_nosym_new set_irr_mode is no more necessary. The input variables of the new routines have been reduced. These routines set u, nirr, npert and these are the only variables that are passed. All the others are passed by USE association. Moreover these routines do not recalculate any more the small group of q. set_irr_sym -> set_irr_sym_new (reduced the number of input parameters) This routine sets t, tmq. sgama_ph -> sgama_ph_new (the array sym is no more needed as input variable) symdyn_munu -> symdyn_munu_new (the array irgq is no more in input variables) symdynph_gq -> symdynph_gq_new (the array irgq is no more in input variables) random_matrix -> random_matrix_new (the array irgq is no more in input variables) dynmat0 -> dynmat0_new (call the new symdyn_munu_new) dynmatrix -> dynmatrix_new (call the new symdyn_munu_new) PAW_dusymmetrize (the array irgq has been removed from the list of input variables, but the name of this routine has not been changed) The old routines are in the file PHonon/PH/obsolete.f90. This file will disapper in the future and the new routines will substitute the old ones, so if you use these routines, you may update the argument list to the new ones or copy the routines that you need in the directory of your application (not advised) and change their names. Moreover soon the array irgq will disappear from phcom. Due to the changes in the organization of the symmetry routines in pw.x now irgq(1)=1, irgq(2)=2, irgq(3)=3, ... and it is no more necessary to use it. It can be safely removed from the routines that use it. If you think that you need it, please create a copy in your common variables. The array was set by smallgq. git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@9273 c92efa57-630b-4861-b058-cf58834340f0
2012-08-08 00:56:57 +08:00
subroutine symdynph_gq_new (xq, phi, s, invs, rtau, irt, nsymq, &
nat, irotmq, minus_q)
!-----------------------------------------------------------------------
!
! This routine receives as input an unsymmetrized dynamical
! matrix expressed on the crystal axes and imposes the symmetry
! of the small group of q. Furthermore it imposes also the symmetry
! q -> -q+G if present.
! February 2020: Update (A. Urru) to include the symmetry operations
! that require the time reversal operator (meaning that TS is a
! symmetry of the crystal). For more information please see:
! Phys. Rev. B 100, 045115 (2019)
!
!
USE kinds, only : DP
USE constants, ONLY: tpi
USE symm_base, ONLY : t_rev
implicit none
!
! The dummy variables
!
Cleanup of the symmetry initialization of the phonon code. Two main changes: The array irgq is removed. The small group of q is calculated only in one routine. The removal of the irgq array changed the list of input parameters of several routines that may be called by external applications linked with the phonon. I have tried not to break the compatibility with these codes adding a suffix _new to the routines that required a change of input parameters. The old routines are still there and can be linked as before, but have been moved to a single file. The old routines are: smallgq -> becomes a routine called set_giq that sets only gi, gimq and finds irotmq if minus_q is .true. It does not recalculate the small group of q. set_irr set_irr_nosym set irr_mode are substituted by the two routines: set_irr_new set_irr_nosym_new set_irr_mode is no more necessary. The input variables of the new routines have been reduced. These routines set u, nirr, npert and these are the only variables that are passed. All the others are passed by USE association. Moreover these routines do not recalculate any more the small group of q. set_irr_sym -> set_irr_sym_new (reduced the number of input parameters) This routine sets t, tmq. sgama_ph -> sgama_ph_new (the array sym is no more needed as input variable) symdyn_munu -> symdyn_munu_new (the array irgq is no more in input variables) symdynph_gq -> symdynph_gq_new (the array irgq is no more in input variables) random_matrix -> random_matrix_new (the array irgq is no more in input variables) dynmat0 -> dynmat0_new (call the new symdyn_munu_new) dynmatrix -> dynmatrix_new (call the new symdyn_munu_new) PAW_dusymmetrize (the array irgq has been removed from the list of input variables, but the name of this routine has not been changed) The old routines are in the file PHonon/PH/obsolete.f90. This file will disapper in the future and the new routines will substitute the old ones, so if you use these routines, you may update the argument list to the new ones or copy the routines that you need in the directory of your application (not advised) and change their names. Moreover soon the array irgq will disappear from phcom. Due to the changes in the organization of the symmetry routines in pw.x now irgq(1)=1, irgq(2)=2, irgq(3)=3, ... and it is no more necessary to use it. It can be safely removed from the routines that use it. If you think that you need it, please create a copy in your common variables. The array was set by smallgq. git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@9273 c92efa57-630b-4861-b058-cf58834340f0
2012-08-08 00:56:57 +08:00
integer :: nat, s (3, 3, 48), irt (48, nat), invs (48), &
nsymq, irotmq
! input: the number of atoms
! input: the symmetry matrices
! input: the rotated of each vector
! input: the small group of q
! input: the inverse of each matrix
! input: the order of the small gro
! input: the rotation sending q ->
real(DP) :: xq (3), rtau (3, 48, nat)
! input: the q point
! input: the R associated at each t
logical :: minus_q
! input: true if a symmetry q->-q+G
complex(DP) :: phi (3, 3, nat, nat)
! inp/out: the matrix to symmetrize
!
! local variables
!
integer :: isymq, sna, snb, irot, na, nb, ipol, jpol, lpol, kpol, &
iflb (nat, nat)
! counters, indices, work space
real(DP) :: arg
! the argument of the phase
complex(DP) :: phip (3, 3, nat, nat), work (3, 3), fase, faseq (48)
! work space, phase factors
!
! We start by imposing hermiticity
!
do na = 1, nat
do nb = 1, nat
do ipol = 1, 3
do jpol = 1, 3
phi (ipol, jpol, na, nb) = 0.5d0 * (phi (ipol, jpol, na, nb) &
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
+ CONJG(phi (jpol, ipol, nb, na) ) )
phi (jpol, ipol, nb, na) = CONJG(phi (ipol, jpol, na, nb) )
enddo
enddo
enddo
enddo
!
! If no other symmetry is present we quit here
!
if ( (nsymq == 1) .and. (.not.minus_q) ) return
!
! Then we impose the symmetry q -> -q+G if present
!
if (minus_q) then
do na = 1, nat
do nb = 1, nat
do ipol = 1, 3
do jpol = 1, 3
work(:,:) = (0.d0, 0.d0)
sna = irt (irotmq, na)
snb = irt (irotmq, nb)
arg = 0.d0
do kpol = 1, 3
arg = arg + (xq (kpol) * (rtau (kpol, irotmq, na) - &
rtau (kpol, irotmq, nb) ) )
enddo
arg = arg * tpi
fase = CMPLX(cos (arg), sin (arg) ,kind=DP)
do kpol = 1, 3
do lpol = 1, 3
work (ipol, jpol) = work (ipol, jpol) + &
s (ipol, kpol, irotmq) * s (jpol, lpol, irotmq) &
* phi (kpol, lpol, sna, snb) * fase
enddo
enddo
phip (ipol, jpol, na, nb) = (phi (ipol, jpol, na, nb) + &
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
CONJG( work (ipol, jpol) ) ) * 0.5d0
enddo
enddo
enddo
enddo
phi = phip
endif
!
! Here we symmetrize with respect to the small group of q
!
if (nsymq == 1) return
iflb (:, :) = 0
do na = 1, nat
do nb = 1, nat
if (iflb (na, nb) == 0) then
work(:,:) = (0.d0, 0.d0)
do isymq = 1, nsymq
Cleanup of the symmetry initialization of the phonon code. Two main changes: The array irgq is removed. The small group of q is calculated only in one routine. The removal of the irgq array changed the list of input parameters of several routines that may be called by external applications linked with the phonon. I have tried not to break the compatibility with these codes adding a suffix _new to the routines that required a change of input parameters. The old routines are still there and can be linked as before, but have been moved to a single file. The old routines are: smallgq -> becomes a routine called set_giq that sets only gi, gimq and finds irotmq if minus_q is .true. It does not recalculate the small group of q. set_irr set_irr_nosym set irr_mode are substituted by the two routines: set_irr_new set_irr_nosym_new set_irr_mode is no more necessary. The input variables of the new routines have been reduced. These routines set u, nirr, npert and these are the only variables that are passed. All the others are passed by USE association. Moreover these routines do not recalculate any more the small group of q. set_irr_sym -> set_irr_sym_new (reduced the number of input parameters) This routine sets t, tmq. sgama_ph -> sgama_ph_new (the array sym is no more needed as input variable) symdyn_munu -> symdyn_munu_new (the array irgq is no more in input variables) symdynph_gq -> symdynph_gq_new (the array irgq is no more in input variables) random_matrix -> random_matrix_new (the array irgq is no more in input variables) dynmat0 -> dynmat0_new (call the new symdyn_munu_new) dynmatrix -> dynmatrix_new (call the new symdyn_munu_new) PAW_dusymmetrize (the array irgq has been removed from the list of input variables, but the name of this routine has not been changed) The old routines are in the file PHonon/PH/obsolete.f90. This file will disapper in the future and the new routines will substitute the old ones, so if you use these routines, you may update the argument list to the new ones or copy the routines that you need in the directory of your application (not advised) and change their names. Moreover soon the array irgq will disappear from phcom. Due to the changes in the organization of the symmetry routines in pw.x now irgq(1)=1, irgq(2)=2, irgq(3)=3, ... and it is no more necessary to use it. It can be safely removed from the routines that use it. If you think that you need it, please create a copy in your common variables. The array was set by smallgq. git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@9273 c92efa57-630b-4861-b058-cf58834340f0
2012-08-08 00:56:57 +08:00
irot = isymq
sna = irt (irot, na)
snb = irt (irot, nb)
arg = 0.d0
do ipol = 1, 3
arg = arg + (xq (ipol) * (rtau (ipol, irot, na) - &
rtau (ipol, irot, nb) ) )
enddo
arg = arg * tpi
faseq (isymq) = CMPLX(cos (arg), sin (arg) ,kind=DP)
do ipol = 1, 3
do jpol = 1, 3
do kpol = 1, 3
do lpol = 1, 3
IF (t_rev(isymq)==1) THEN
work (ipol, jpol) = work (ipol, jpol) + &
s (ipol, kpol, irot) * s (jpol, lpol, irot) &
* CONJG(phi (kpol, lpol, sna, snb) * faseq (isymq))
ELSE
work (ipol, jpol) = work (ipol, jpol) + &
s (ipol, kpol, irot) * s (jpol, lpol, irot) &
* phi (kpol, lpol, sna, snb) * faseq (isymq)
ENDIF
enddo
enddo
enddo
enddo
enddo
do isymq = 1, nsymq
Cleanup of the symmetry initialization of the phonon code. Two main changes: The array irgq is removed. The small group of q is calculated only in one routine. The removal of the irgq array changed the list of input parameters of several routines that may be called by external applications linked with the phonon. I have tried not to break the compatibility with these codes adding a suffix _new to the routines that required a change of input parameters. The old routines are still there and can be linked as before, but have been moved to a single file. The old routines are: smallgq -> becomes a routine called set_giq that sets only gi, gimq and finds irotmq if minus_q is .true. It does not recalculate the small group of q. set_irr set_irr_nosym set irr_mode are substituted by the two routines: set_irr_new set_irr_nosym_new set_irr_mode is no more necessary. The input variables of the new routines have been reduced. These routines set u, nirr, npert and these are the only variables that are passed. All the others are passed by USE association. Moreover these routines do not recalculate any more the small group of q. set_irr_sym -> set_irr_sym_new (reduced the number of input parameters) This routine sets t, tmq. sgama_ph -> sgama_ph_new (the array sym is no more needed as input variable) symdyn_munu -> symdyn_munu_new (the array irgq is no more in input variables) symdynph_gq -> symdynph_gq_new (the array irgq is no more in input variables) random_matrix -> random_matrix_new (the array irgq is no more in input variables) dynmat0 -> dynmat0_new (call the new symdyn_munu_new) dynmatrix -> dynmatrix_new (call the new symdyn_munu_new) PAW_dusymmetrize (the array irgq has been removed from the list of input variables, but the name of this routine has not been changed) The old routines are in the file PHonon/PH/obsolete.f90. This file will disapper in the future and the new routines will substitute the old ones, so if you use these routines, you may update the argument list to the new ones or copy the routines that you need in the directory of your application (not advised) and change their names. Moreover soon the array irgq will disappear from phcom. Due to the changes in the organization of the symmetry routines in pw.x now irgq(1)=1, irgq(2)=2, irgq(3)=3, ... and it is no more necessary to use it. It can be safely removed from the routines that use it. If you think that you need it, please create a copy in your common variables. The array was set by smallgq. git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@9273 c92efa57-630b-4861-b058-cf58834340f0
2012-08-08 00:56:57 +08:00
irot = isymq
sna = irt (irot, na)
snb = irt (irot, nb)
do ipol = 1, 3
do jpol = 1, 3
phi (ipol, jpol, sna, snb) = (0.d0, 0.d0)
do kpol = 1, 3
do lpol = 1, 3
IF (t_rev(isymq)==1) THEN
phi(ipol,jpol,sna,snb)=phi(ipol,jpol,sna,snb) &
+ s(ipol,kpol,invs(irot))*s(jpol,lpol,invs(irot))&
* CONJG(work (kpol, lpol)*faseq (isymq))
ELSE
phi(ipol,jpol,sna,snb)=phi(ipol,jpol,sna,snb) &
+ s(ipol,kpol,invs(irot))*s(jpol,lpol,invs(irot))&
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
* work (kpol, lpol) * CONJG(faseq (isymq) )
ENDIF
enddo
enddo
enddo
enddo
iflb (sna, snb) = 1
enddo
endif
enddo
enddo
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
phi (:, :, :, :) = phi (:, :, :, :) / DBLE(nsymq)
return
Cleanup of the symmetry initialization of the phonon code. Two main changes: The array irgq is removed. The small group of q is calculated only in one routine. The removal of the irgq array changed the list of input parameters of several routines that may be called by external applications linked with the phonon. I have tried not to break the compatibility with these codes adding a suffix _new to the routines that required a change of input parameters. The old routines are still there and can be linked as before, but have been moved to a single file. The old routines are: smallgq -> becomes a routine called set_giq that sets only gi, gimq and finds irotmq if minus_q is .true. It does not recalculate the small group of q. set_irr set_irr_nosym set irr_mode are substituted by the two routines: set_irr_new set_irr_nosym_new set_irr_mode is no more necessary. The input variables of the new routines have been reduced. These routines set u, nirr, npert and these are the only variables that are passed. All the others are passed by USE association. Moreover these routines do not recalculate any more the small group of q. set_irr_sym -> set_irr_sym_new (reduced the number of input parameters) This routine sets t, tmq. sgama_ph -> sgama_ph_new (the array sym is no more needed as input variable) symdyn_munu -> symdyn_munu_new (the array irgq is no more in input variables) symdynph_gq -> symdynph_gq_new (the array irgq is no more in input variables) random_matrix -> random_matrix_new (the array irgq is no more in input variables) dynmat0 -> dynmat0_new (call the new symdyn_munu_new) dynmatrix -> dynmatrix_new (call the new symdyn_munu_new) PAW_dusymmetrize (the array irgq has been removed from the list of input variables, but the name of this routine has not been changed) The old routines are in the file PHonon/PH/obsolete.f90. This file will disapper in the future and the new routines will substitute the old ones, so if you use these routines, you may update the argument list to the new ones or copy the routines that you need in the directory of your application (not advised) and change their names. Moreover soon the array irgq will disappear from phcom. Due to the changes in the organization of the symmetry routines in pw.x now irgq(1)=1, irgq(2)=2, irgq(3)=3, ... and it is no more necessary to use it. It can be safely removed from the routines that use it. If you think that you need it, please create a copy in your common variables. The array was set by smallgq. git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@9273 c92efa57-630b-4861-b058-cf58834340f0
2012-08-08 00:56:57 +08:00
end subroutine symdynph_gq_new