Statistiques
| Révision :

root / src / VectorPer.f90 @ 2

Historique | Voir | Annoter | Télécharger (1,41 ko)

1
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2
!
3
! VectorPer
4
!
5
!!!!!!!!!!!!!!!!!!!!!!!
6
!
7
! This subroutine caclulates the vector defined by atom i and j
8
! with j being displaced to a periodic image of the system.
9
!
10
! Input:
11
!  i: (INTEGER) index of the first atom, in the central cell
12
!  j: (INTEGER) index of the second atom, in a periodic image
13
!  na,nb,nc: (INTEGER) number of displacement of j atom, in lattice vectors.
14
!  x(Nat), y(nat), z(nat) : (REAL) Cartesian coordinates of the system.
15
!
16
! Output:
17
! vx,vy,vz: (REAL) Vector i->j
18
! Norm:     (REAL) Norm of the vector.
19
!
20
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
21
!
22
! Nat and Lattice vectors (lat_a, lat_b, lat_c) are taken from Path_Module
23
!
24
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
25

    
26
      SUBROUTINE VectorPer(n1,n2,na,nb,nc,x,y,z,vx,vy,vz,norm)
27

    
28
        use VarTypes
29
        use Path_module, only : NAt,Lat_a,Lat_b,Lat_c
30

    
31
        integer(KINT) :: n1,n2
32
        INTEGER(KINT) :: na,nb,nc
33
        real(KREAL) ::  x(Nat),y(Nat),z(Nat)
34
        real(KREAL) ::  vx,vy,vz,norm
35

    
36
        vx=x(n2)-x(n1)+na*Lat_a(1)+nb*Lat_b(1)+nc*Lat_c(1)
37
        vy=y(n2)-y(n1)+na*Lat_a(2)+nb*Lat_b(2)+nc*Lat_c(2)
38
        vz=z(n2)-z(n1)+na*Lat_a(3)+nb*Lat_b(3)+nc*Lat_c(3)
39

    
40
        norm=dsqrt( vx*vx + vy*vy + vz*vz )
41

    
42
!       write(6,*) "Dbg VectorPer : n1,n2, na,nb,nc :",n1,n2,na,nb,nc
43
!       write(6,*) vx,vy,vz,norm
44
!       write(6,*) 
45

    
46
	RETURN
47
      END SUBROUTINE VectorPer