Incorrect detection of inversion symmetry in phonons fixed (Phil Wang, JHU).

I think a better fix would be to move the detection of the inversion symmetry
into function "copy_sym" (not making assumptions on which operation is the
inversion, and transforming the function into a subroutine) but this must be
done with care and far from a release. The current fix seem to be 100% safe.
This commit is contained in:
Paolo Giannozzi 2020-08-03 19:20:31 +02:00
parent b950fe0200
commit e5cff91a5d
2 changed files with 19 additions and 9 deletions

View File

@ -30,7 +30,7 @@ SUBROUTINE set_small_group_of_q(nsymq, invsymq, minus_q)
LOGICAL, INTENT(INOUT) :: minus_q, invsymq
!
REAL(DP), ALLOCATABLE :: rtau(:,:,:)
INTEGER :: isym
LOGICAL :: sym(48)
!
sym(1:nsym)=.true.
@ -55,11 +55,16 @@ SUBROUTINE set_small_group_of_q(nsymq, invsymq, minus_q)
!
CALL inverse_s ( )
!
! check if inversion (I) is a symmetry. If so, there should be nsymq/2
! symmetries without inversion, followed by nsymq/2 with inversion
! Since identity is always s(:,:,1), inversion should be s(:,:,1+nsymq/2)
! Check if inversion (I) is a symmetry
! Note that the first symmetry operation is always the identity (E)
!
invsymq = ALL ( s(:,:,nsymq/2+1) == -s(:,:,1) )
invsymq =.FALSE.
DO isym = 1, nsymq
IF ( ALL ( s(:,:,isym) == -s(:,:,1) ) ) THEN
invsymq = .TRUE.
EXIT
END IF
END DO
!
! Since the order of the s matrices is changed we need to recalculate:
!

View File

@ -139,12 +139,17 @@ SUBROUTINE lr_smallgq (xq)
!
ENDDO
!
! Check if inversion (I) is a symmetry. If so, there should be nsymq/2
! symmetries without inversion, followed by nsymq/2 with inversion
! Since identity is always s(:,:,1), inversion should be s(:,:,1+nsymq/2)
! Check if inversion (I) is a symmetry
! Note that the first symmetry operation is always the identity (E)
! IT: it seems that invsymq is useless (used nowhere)...
!
invsymq = ALL ( s(:,:,nsymq/2+1) == -s(:,:,1) )
invsymq =.FALSE.
DO isym = 1, nsymq
IF ( ALL ( s(:,:,isym) == -s(:,:,1) ) ) THEN
invsymq = .TRUE.
EXIT
END IF
END DO
!
! The order of the s matrices has changed.
! Transform symmetry matrices s from crystal to cartesian axes.