TABLE OF CONTENTS


ABINIT/dfpt_sydy [ Functions ]

[ Top ] [ Functions ]

NAME

 dfpt_sydy

FUNCTION

 Symmetrize dynamical matrix (eventually diagonal wrt to the atoms)
 Unsymmetrized dynamical matrix   is  input as dyfrow;
 symmetrized dynamical matrix is then  placed in sdyfro.
 If nsym=1 simply copy dyfrow   into sdyfro.

COPYRIGHT

 Copyright (C) 1999-2018 ABINIT group (XG,MT)
 This file is distributed under the terms of the
 GNU General Public License, see ~abinit/COPYING
 or http://www.gnu.org/copyleft/gpl.txt .
 For the initials of contributors, see ~abinit/doc/developers/contributors.txt .

INPUTS

  cplex=1 if dynamical matrix is real, 2 if it is complex
  dyfrow(3,3,natom,1+(natom-1)*nondiag)=unsymmetrized dynamical matrix
  indsym(4,msym*natom)=indirect indexing array: for each
   isym,iatom, fourth element is label of atom into which iatom is sent by
   INVERSE of symmetry operation isym; first three elements are the primitive
   translations which must be subtracted after the transformation to get back
   to the original unit cell.
  natom=number of atoms in cell.
  nondiag=0 if dynamical matrix is     diagonal with respect to atoms
  nsym=number of symmetry operators in group.
  qphon(3)=wavevector of the phonon
  symq(4,2,nsym)=1 if symmetry preserves present qpoint. From littlegroup_q
  symrec(3,3,nsym)=symmetries of group in terms of operations on real
    space primitive translations (integers).

OUTPUT

  sdyfro(3,3,natom,1+(natom-1)*nondiag)=symmetrized dynamical matrix

NOTES

 Symmetrization of gradients with respect to reduced
 coordinates tn is conducted according to the expression
 $[d(e)/d(t(n,a))]_{symmetrized} = (1/Nsym)*Sum(S)*symrec(n,m,S)*
              [d(e)/d(t(m,b))]_{unsymmetrized}$
 where $t(m,b)= (symrel^{-1})(m,n)*(t(n,a)-tnons(n))$ and tnons
 is a possible nonsymmorphic translation.  The label "b" here
 refers to the atom which gets rotated into "a" under symmetry "S".
 symrel is the symmetry matrix in real space, which is the inverse
 transpose of symrec.  symrec is the symmetry matrix in reciprocal
 space.  $sym_{cartesian} = R * symrel * R^{-1} = G * symrec * G^{-1}$
 where the columns of R and G are the dimensional primitive translations
 in real and reciprocal space respectively.
 Note the use of "symrec" in the symmetrization expression above.

PARENTS

      dfpt_dyfro

CHILDREN

SOURCE

 62 #if defined HAVE_CONFIG_H
 63 #include "config.h"
 64 #endif
 65 
 66 #include "abi_common.h"
 67 
 68 
 69 subroutine dfpt_sydy(cplex,dyfrow,indsym,natom,nondiag,nsym,qphon,sdyfro,symq,symrec)
 70 
 71  use defs_basis
 72  use m_profiling_abi
 73 
 74 !This section has been created automatically by the script Abilint (TD).
 75 !Do not modify the following lines by hand.
 76 #undef ABI_FUNC
 77 #define ABI_FUNC 'dfpt_sydy'
 78 !End of the abilint section
 79 
 80  implicit none
 81 
 82 !Arguments -------------------------------
 83 !scalars
 84  integer,intent(in) :: cplex,natom,nondiag,nsym
 85 !arrays
 86  integer,intent(in) :: indsym(4,nsym,natom),symq(4,2,nsym),symrec(3,3,nsym)
 87  real(dp),intent(in) :: dyfrow(cplex,3,3,natom,1+(natom-1)*nondiag),qphon(3)
 88  real(dp),intent(out) :: sdyfro(cplex,3,3,natom,1+(natom-1)*nondiag)
 89 
 90 !Local variables -------------------------
 91 !scalars
 92  integer :: ia,indi,indj,isym,ja,kappa,mu,natom_nondiag,nsym_used,nu
 93  logical :: qeq0
 94  real(dp) :: arg,div,phasei,phaser
 95 !arrays
 96  real(dp) :: work(cplex,3,3)
 97 
 98 ! *********************************************************************
 99 
100  if (nsym==1) then
101 
102 !  Only symmetry is identity so simply copy
103    sdyfro(:,:,:,:,:)=dyfrow(:,:,:,:,:)
104 
105  else
106 
107 !  Actually carry out symmetrization
108    sdyfro(:,:,:,:,:)=zero
109    qeq0=(qphon(1)**2+qphon(2)**2+qphon(3)**2<1.d-14)
110 !  === Diagonal dyn. matrix OR q=0
111    if (nondiag==0.or.qeq0) then
112      natom_nondiag=1;if (nondiag==1) natom_nondiag=natom
113      do ja=1,natom_nondiag
114        do ia=1,natom
115          do isym=1,nsym
116            indi=indsym(4,isym,ia)
117            indj=1;if (nondiag==1) indj=indsym(4,isym,ja)
118            work(:,:,:)=zero
119            do mu=1,3
120              do nu=1,3
121                do kappa=1,3
122                  work(:,mu,kappa)=work(:,mu,kappa)+symrec(mu,nu,isym)*dyfrow(:,nu,kappa,indi,indj)
123                end do
124              end do
125            end do
126            do mu=1,3
127              do nu=1,3
128                do kappa=1,3
129                  sdyfro(:,kappa,mu,ia,ja)=sdyfro(:,kappa,mu,ia,ja)+symrec(mu,nu,isym)*work(:,kappa,nu)
130                end do
131              end do
132            end do
133          end do
134        end do
135      end do
136      div=one/dble(nsym)
137      sdyfro(:,:,:,:,:)=div*sdyfro(:,:,:,:,:)
138 !    === Non diagonal dyn. matrix AND q<>0
139    else
140      do ja=1,natom
141        do ia=1,natom
142          nsym_used=0
143          do isym=1,nsym
144            if (symq(4,1,isym)==1) then
145              arg=two_pi*(qphon(1)*(indsym(1,isym,ia)-indsym(1,isym,ja)) &
146 &             +qphon(2)*(indsym(2,isym,ia)-indsym(2,isym,ja)) &
147 &             +qphon(3)*(indsym(3,isym,ia)-indsym(3,isym,ja)))
148              phaser=cos(arg);phasei=sin(arg)
149              nsym_used=nsym_used+1
150              indi=indsym(4,isym,ia)
151              indj=indsym(4,isym,ja)
152              work(:,:,:)=zero
153              do mu=1,3
154                do nu=1,3
155                  do kappa=1,3
156                    work(:,mu,kappa)=work(:,mu,kappa)+symrec(mu,nu,isym)*dyfrow(:,nu,kappa,indi,indj)
157                  end do
158                end do
159              end do
160              do mu=1,3
161                do nu=1,3
162                  do kappa=1,3
163                    sdyfro(1,kappa,mu,ia,ja)=sdyfro(1,kappa,mu,ia,ja) &
164 &                   +symrec(mu,nu,isym)*(work(1,kappa,nu)*phaser-work(2,kappa,nu)*phasei)
165                  end do
166                end do
167              end do
168              if (cplex==2) then
169                do mu=1,3
170                  do nu=1,3
171                    do kappa=1,3
172                      sdyfro(2,kappa,mu,ia,ja)=sdyfro(2,kappa,mu,ia,ja) &
173 &                     +symrec(mu,nu,isym)*(work(1,kappa,nu)*phasei+work(2,kappa,nu)*phaser)
174                    end do
175                  end do
176                end do
177              end if
178            end if
179          end do
180          div=one/dble(nsym_used)
181          sdyfro(:,:,:,ia,ja)=div*sdyfro(:,:,:,ia,ja)
182        end do
183      end do
184    end if
185 
186  end if
187 
188 end subroutine dfpt_sydy