Statistiques
| Révision :

root / src / CalcCnct.f90 @ 4

Historique | Voir | Annoter | Télécharger (3,72 ko)

1
!================================================================
2
! Calculation of the connectivity.
3
!
4
! Input:
5
! Na: (INTEGER) Number of atoms in the system
6
! Atome: (INTEGER) Number of mass of the atoms.
7
!                  Needed to find their covalent raii.
8
!  x(Nat), y(nat), z(nat) : (REAL) Cartesian coordinates of the system.
9
!  LIAISONS: (INTEGER Na,0:NMaxL) Array containing the connectivity.
10
!            That is Liaisons(i,:) contains the atoms linked to i.
11
!            Liaisons(i,0) contains the number of atoms linked to i.
12
! r_cov(0:Max_Z) (REAL) Covalent radii
13
! Fact (REAL) Factor used to determined if two atoms are linked :
14
!            i and j are linked if (dist(i,j)*fact <= rcov(i)+rcov(j)
15
!
16
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
17
! Taken from Path_Module
18
! NMaxL (INTEGER): Maximum number of bonds for one atome
19
! Max_Z (INTEGER): Last atom for which I have the atomic of mass and covalent radii.
20
! Nom(Nat) (STRING): Name of the atoms.
21
! Prog (SCHARS): Name of the program used to calculate energies and gradients
22
!
23
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
24
! v1.0 (c) PFL
25
! v1.1 (c) PFL 11.2007
26
! A test has been added for periodic system, ie the linked test
27
! is done between i in the central cell, and j in all surrounding cells.
28
!
29
!================================================================
30

    
31
SUBROUTINE CalcCnct(na,atome,x,y,z,LIAISONS,r_cov,fact)
32

    
33
  use Path_module, only : NMaxL, max_Z,Nom,Prog, KINT, KREAL
34

    
35
  character(2) :: ATOM
36
  integer(KINT) :: na,atome(Na),at,ind_zmat(Na,5),long
37
  real(KREAL) ::  x(Na),y(Na),z(Na),fact
38
  real(KREAL) :: vx,vy,vz,dist
39
  REAL(KREAL) :: r_cov(0:Max_Z)
40
  INTEGER(KINT) :: LIAISONS(Na,0:NMaxL),Nbli,Nblj
41

    
42
  ! For periodic systems
43
  INTEGER(KINT) :: Ka,Kb,Kc
44
  LOGICAL   :: Bound
45

    
46
  ! Internals
47
  logical(KREAL) ::debug
48

    
49
  INTERFACE
50
     function valid(string) result (isValid)
51
       CHARACTER(*), intent(in) :: string
52
       logical                  :: isValid
53
     END function VALID
54
  END INTERFACE
55

    
56
  debug=valid('calccnct')
57
  if (debug) WRITE(*,*) "======================= Entering CalcCnct ======================="
58

    
59
  DO i=1,na
60
     Liaisons(i,0)=0
61
  END DO
62

    
63
  if (debug) THEN
64
     WRITE(*,*) 'CalcCnct'
65
     DO iat=1,na
66
        i=atome(iat)
67
        WRITE(*,*) Nom(I),I,r_cov(i),r_cov(i)*fact
68
     END DO
69
  END IF
70

    
71
  IF (PROG/="VASP") THEN
72
     DO i=1,na
73
        NbLi=LIAISONS(i,0)
74
        DO j=i+1,na
75
           CALL vecteur(j,i,x,y,z,vx,vy,vz,dist)
76
           dist=dist/fact
77
           distth=(r_cov(atome(i))+r_cov(atome(j)))/100.
78
!           if (debug) WRITE(*,*) atome(i),atome(j),dist,distth
79
           if (dist.le.distth) THEN
80
              NbLi=NbLi+1
81
              LIAISONS(i,NbLi)=j;
82
              NBlj=LIAISONS(j,0)+1
83
              LIAISONS(j,Nblj)=i;
84
              LIAISONS(j,0)=Nblj
85
           END IF
86
        END DO
87
        LIAISONS(i,0)=Nbli
88
     END DO
89
  ELSE
90
     DO i=1,na
91
        NbLi=LIAISONS(i,0)
92
        DO j=i+1,na
93
           Bound=.FALSE.
94
           DO ka=-1,1
95
              DO Kb=-1,1
96
                 DO Kc=-1,1
97
                    CALL VectorPer(j,i,ka,kb,kc,x,y,z,vx,vy,vz,dist)
98
                    dist=dist/fact
99
                    distth=(r_cov(atome(i))+r_cov(atome(j)))/100.
100
!                    if (debug) WRITE(*,*) atome(i),atome(j),dist,distth
101
                    if (dist.le.distth) Bound=.TRUE.
102
                 END DO
103
              END DO
104
           END DO
105
           IF (Bound) THEN
106
              if (debug) WRITE(*,*) "Adding a bond between:",i,j
107
              NbLi=NbLi+1
108
              LIAISONS(i,NbLi)=j;
109
              NBlj=LIAISONS(j,0)+1
110
              LIAISONS(j,Nblj)=i;
111
              LIAISONS(j,0)=Nblj
112
           END IF
113
        END DO
114
        LIAISONS(i,0)=Nbli
115
     END DO
116
  END IF
117
  if (debug) WRITE(*,*) "======================= CalcCnct  over ======================="
118
END SUBROUTINE CalcCnct