root / src / cmshft.f90 @ 4
Historique | Voir | Annoter | Télécharger (1,61 ko)
1 |
subroutine cmshft(natom,rx,ry,rz,rmass,cmx,cmy,cmz,ishift) |
---|---|
2 |
!c |
3 |
!c shifts all x, y, and z coordinates passed in rx,ry,rz to keep |
4 |
!c the center of mass at the origin if ishift is not zero. otherwise |
5 |
!c cmx, cmy, and cmz return the center of mass coordinates and no |
6 |
!c shift is performed. coordinate and mass units arbitrary. |
7 |
!c |
8 |
|
9 |
use VarTypes |
10 |
use Io_module |
11 |
|
12 |
IMPLICIT NONE |
13 |
|
14 |
|
15 |
! Number of atoms |
16 |
INTEGER(KINT), INTENT(IN) :: NAtom |
17 |
! Coordinates and masses |
18 |
REAL(KREAL), DIMENSION(NAtom) :: rx,ry,rz,rmass |
19 |
! Center of mass coordinates |
20 |
real(KREAL) :: cmx,cmy,cmz |
21 |
! Flag if user wants to shift center of mass to origin |
22 |
INTEGER(KINT) :: IShift |
23 |
|
24 |
REAL(KREAL), parameter :: zero=0.d0,one=1.d0 |
25 |
INTEGER(KINT) :: i,j |
26 |
REAL(KREAL) :: TmassI, tmass |
27 |
|
28 |
if(natom.le.0) then |
29 |
if(IOOUT.gt.0) write(IOOUT,'(/2a/)') & |
30 |
' *** error, illegal array dimension in cmshft,', & |
31 |
' return without action ***' |
32 |
return |
33 |
end if |
34 |
!c |
35 |
!c calculate center of mass coordinates |
36 |
!c |
37 |
tmass=rmass(1) |
38 |
do j=2,natom |
39 |
tmass=tmass+rmass(j) |
40 |
END DO |
41 |
!c |
42 |
!c DO i=1,natom |
43 |
!c write(IOOUT,'(4F15.3)') rmass(i),rx(i),ry(i),rz(i) |
44 |
!c END DO |
45 |
|
46 |
cmx=zero |
47 |
cmy=zero |
48 |
cmz=zero |
49 |
do j=1,natom |
50 |
cmx=rmass(j)*rx(j)+cmx |
51 |
cmy=rmass(j)*ry(j)+cmy |
52 |
cmz=rmass(j)*rz(j)+cmz |
53 |
END DO |
54 |
|
55 |
tmassi=one/tmass |
56 |
cmx=cmx*tmassi |
57 |
cmy=cmy*tmassi |
58 |
cmz=cmz*tmassi |
59 |
!c |
60 |
!c optional shift of all cartesian coordinates |
61 |
!c |
62 |
if(ishift.ne.0) then |
63 |
do j=1,natom |
64 |
rx(j)=rx(j)-cmx |
65 |
ry(j)=ry(j)-cmy |
66 |
rz(j)=rz(j)-cmz |
67 |
END DO |
68 |
end if |
69 |
|
70 |
return |
71 |
end subroutine cmshft |