Statistiques
| Révision :

root / src / CalcCnct.f90

Historique | Voir | Annoter | Télécharger (5,16 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
!----------------------------------------------------------------------
34
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon, 
35
!  Centre National de la Recherche Scientifique,
36
!  Université Claude Bernard Lyon 1. All rights reserved.
37
!
38
!  This work is registered with the Agency for the Protection of Programs 
39
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
40
!
41
!  Authors: P. Fleurat-Lessard, P. Dayal
42
!  Contact: optnpath@gmail.com
43
!
44
! This file is part of "Opt'n Path".
45
!
46
!  "Opt'n Path" is free software: you can redistribute it and/or modify
47
!  it under the terms of the GNU Affero General Public License as
48
!  published by the Free Software Foundation, either version 3 of the License,
49
!  or (at your option) any later version.
50
!
51
!  "Opt'n Path" is distributed in the hope that it will be useful,
52
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
53
!
54
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
55
!  GNU Affero General Public License for more details.
56
!
57
!  You should have received a copy of the GNU Affero General Public License
58
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
59
!
60
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
61
! for commercial licensing opportunities.
62
!----------------------------------------------------------------------
63

    
64
  use Path_module, only : NMaxL, max_Z,Nom, KINT, KREAL, FPBC, &
65
       kaBeg,kaEnd,kbBeg,kbEnd,kcBeg,kcEnd
66
  
67
  IMPLICIT NONE
68

    
69
  integer(KINT) :: na, atome(Na)
70
  real(KREAL) ::  x(Na),y(Na),z(Na),fact
71
  real(KREAL) :: vx,vy,vz,dist
72
  REAL(KREAL) :: r_cov(0:Max_Z)
73
  INTEGER(KINT) :: LIAISONS(Na,0:NMaxL),Nbli,Nblj
74

    
75
  ! For periodic systems
76
  INTEGER(KINT) :: Ka,Kb,Kc
77
  LOGICAL   :: Bound
78

    
79
  ! Internals
80
  logical(KREAL) ::debug
81
  REAL(KREAL) :: DistTh
82
  INTEGER(KINT) :: I,j,iat
83

    
84
  INTERFACE
85
     function valid(string) result (isValid)
86
       CHARACTER(*), intent(in) :: string
87
       logical                  :: isValid
88
     END function VALID
89
  END INTERFACE
90

    
91
  debug=valid('calccnct')
92
  if (debug)  Call Header (" Entering CalcCnct ")
93

    
94
  DO i=1,na
95
     Liaisons(i,0)=0
96
  END DO
97

    
98
  if (debug) THEN
99
     WRITE(*,*) 'CalcCnct : covalent radii used'
100
     DO iat=1,na
101
        i=atome(iat)
102
        WRITE(*,*) Nom(I),I,r_cov(i)*fact
103
     END DO
104
     WRITE(*,*) 'Coordinates'
105
     DO iat=1,na
106
        i=atome(iat)
107
        WRITE(*,*) Nom(I),x(iat),y(iat),z(iat)
108
     END DO
109
  END IF
110

    
111
  IF (FPBC) THEN
112
     DO i=1,na
113
        NbLi=LIAISONS(i,0)
114
        DO j=i+1,na
115
           Bound=.FALSE.
116
           DO ka=kaBeg,kaEnd
117
              DO Kb=kbBeg,kbEnd
118
                 DO Kc=kcBeg,kcEnd
119
                    CALL VectorPer(j,i,ka,kb,kc,x,y,z,vx,vy,vz,dist)
120
                    dist=dist/fact
121
                    distth=(r_cov(atome(i))+r_cov(atome(j)))/100.
122
!                    if (debug) WRITE(*,*) atome(i),atome(j),dist,distth
123
                    if (dist.le.distth) Bound=.TRUE.
124
                 END DO
125
              END DO
126
           END DO
127
           IF (Bound) THEN
128
              if (debug) WRITE(*,*) "Adding a bond between:",i,j
129
              NbLi=NbLi+1
130
              LIAISONS(i,NbLi)=j;
131
              NBlj=LIAISONS(j,0)+1
132
              LIAISONS(j,Nblj)=i;
133
              LIAISONS(j,0)=Nblj
134
           END IF
135
        END DO
136
        LIAISONS(i,0)=Nbli
137
     END DO
138
  ELSE
139
     DO i=1,na
140
        NbLi=LIAISONS(i,0)
141
        DO j=i+1,na
142
           CALL vecteur(j,i,x,y,z,vx,vy,vz,dist)
143
           dist=dist/fact
144
           distth=(r_cov(atome(i))+r_cov(atome(j)))/100.
145
!           if (debug) WRITE(*,*) atome(i),atome(j),dist,distth
146
           if (dist.le.distth) THEN
147
              NbLi=NbLi+1
148
              LIAISONS(i,NbLi)=j;
149
              NBlj=LIAISONS(j,0)+1
150
              LIAISONS(j,Nblj)=i;
151
              LIAISONS(j,0)=Nblj
152
           END IF
153
        END DO
154
        LIAISONS(i,0)=Nbli
155
     END DO
156
  END IF
157
  if (debug) Call Header (" CalcCnct over ")
158
END SUBROUTINE CalcCnct