The Elk Code
symdmat.f90
Go to the documentation of this file.
1 
2 ! Copyright (C) 2007 F. Bultmark, F. Cricchio, L. Nordstrom and J. K. Dewhurst.
3 ! This file is distributed under the terms of the GNU General Public License.
4 ! See the file COPYING for license details.
5 
6 subroutine symdmat(lmax,ld,dmat)
7 use modmain
8 implicit none
9 ! arguments
10 integer, intent(in) :: lmax,ld
11 complex(8), intent(inout) :: dmat(ld,nspinor,ld,nspinor,natmtot)
12 ! local variables
13 integer is,ia,ja,ias,jas
14 integer isym,lspl,lspn,lmmax
15 real(8) t1
16 ! allocatable arrays
17 complex(8), allocatable :: dm(:,:,:,:,:)
18 lmmax=(lmax+1)**2
19 ! allocate local arrays
20 allocate(dm(ld,nspinor,ld,nspinor,natmmax))
21 t1=1.d0/dble(nsymcrys)
22 do is=1,nspecies
23 ! make copy of the density matrices
24  do ia=1,natoms(is)
25  ias=idxas(ia,is)
26  dm(1:lmmax,:,1:lmmax,:,ia)=dmat(1:lmmax,:,1:lmmax,:,ias)
27  end do
28 ! loop over atoms
29  do ia=1,natoms(is)
30 ! only symmetrise first equivalent atom (rotate into others)
31  if (.not.tfeqat(ia,is)) cycle
32  ias=idxas(ia,is)
33  dmat(:,:,:,:,ias)=0.d0
34  do isym=1,nsymcrys
35  lspl=lsplsymc(isym)
36  lspn=lspnsymc(isym)
37 ! equivalent atom index (symmetry rotates atom ja into atom ia)
38  ja=ieqatom(ia,is,isym)
39  call rotdmat(symlatc(:,:,lspl),symlatc(:,:,lspn),lmax,nspinor,ld, &
40  dm(:,:,:,:,ja),dmat(:,:,:,:,ias))
41 ! end loop over crystal symmetries
42  end do
43 ! normalise
44  dmat(:,:,:,:,ias)=t1*dmat(:,:,:,:,ias)
45 ! rotate into equivalent atoms
46  do ja=1,natoms(is)
47  if (eqatoms(ia,ja,is).and.(ia /= ja)) then
48  isym=findloc(ieqatom(ia,is,1:nsymcrys),ja,1)
49  jas=idxas(ja,is)
50 ! inverse symmetry (which rotates atom ia into atom ja)
51  lspl=isymlat(lsplsymc(isym))
52  lspn=isymlat(lspnsymc(isym))
53  dmat(:,:,:,:,jas)=0.d0
54  call rotdmat(symlatc(:,:,lspl),symlatc(:,:,lspn),lmax,nspinor,ld, &
55  dmat(:,:,:,:,ias),dmat(:,:,:,:,jas))
56  end if
57  end do
58 ! end loop over atoms and species
59  end do
60 end do
61 deallocate(dm)
62 end subroutine
63 
integer, dimension(maxsymcrys) lspnsymc
Definition: modmain.f90:366
integer natmmax
Definition: modmain.f90:38
logical, dimension(:,:), allocatable tfeqat
Definition: modmain.f90:372
integer, dimension(maxatoms, maxspecies) idxas
Definition: modmain.f90:42
integer nsymcrys
Definition: modmain.f90:358
integer, dimension(48) isymlat
Definition: modmain.f90:348
logical, dimension(:,:,:), allocatable eqatoms
Definition: modmain.f90:370
integer, dimension(:,:,:), allocatable ieqatom
Definition: modmain.f90:368
integer, dimension(maxsymcrys) lsplsymc
Definition: modmain.f90:364
subroutine symdmat(lmax, ld, dmat)
Definition: symdmat.f90:7
real(8), dimension(3, 3, 48) symlatc
Definition: modmain.f90:350
integer, dimension(maxspecies) natoms
Definition: modmain.f90:36
subroutine rotdmat(rspl, rspn, lmax, nspinor, ld, dmat1, dmat2)
Definition: rotdmat.f90:7
integer nspecies
Definition: modmain.f90:34