Statistiques
| Révision :

root / src / Extrapol_mixed.f90

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

1
SUBROUTINE Extrapol_mixed(s,dist,x0,y0,z0,xgeom,Coef)
2

    
3
! This subroutine constructs the path, and if dist<>Infinity, it samples
4
! the path to obtain geometries.
5
! Basically, you call it twice: i) dist=infinity, it will calculate the 
6
! length of the path
7
! ii) dist finite, it will give you the images you want along the path.
8
!
9
! For now, it gives equidistant geometries
10
!!!!!!!!!!!!!!!!
11
!
12
! v2.0
13
! Uses Mix2cart for conversions.
14

    
15
!----------------------------------------------------------------------
16
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon, 
17
!  Centre National de la Recherche Scientifique,
18
!  Université Claude Bernard Lyon 1. All rights reserved.
19
!
20
!  This work is registered with the Agency for the Protection of Programs 
21
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
22
!
23
!  Authors: P. Fleurat-Lessard, P. Dayal
24
!  Contact: optnpath@gmail.com
25
!
26
! This file is part of "Opt'n Path".
27
!
28
!  "Opt'n Path" is free software: you can redistribute it and/or modify
29
!  it under the terms of the GNU Affero General Public License as
30
!  published by the Free Software Foundation, either version 3 of the License,
31
!  or (at your option) any later version.
32
!
33
!  "Opt'n Path" is distributed in the hope that it will be useful,
34
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
35
!
36
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
37
!  GNU Affero General Public License for more details.
38
!
39
!  You should have received a copy of the GNU Affero General Public License
40
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
41
!
42
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
43
! for commercial licensing opportunities.
44
!----------------------------------------------------------------------
45

    
46

    
47
  use Path_module
48
  use Io_module
49

    
50

    
51
  IMPLICIT NONE
52

    
53

    
54
  REAL(KREAL), INTENT(OUT) :: s
55
  REAL(KREAL), INTENT(IN) :: dist,X0(Nat),Y0(Nat),Z0(Nat)
56
  REAL(KREAL), INTENT(IN) :: Xgeom(NGeomI),Coef(NGeomI,NCoord)
57

    
58
  INTEGER(KINT) :: IdxGeom, I, J, K, Idx
59
  REAL(KREAL) :: Rmsd, MRot(3, 3), ds, u
60

    
61
  REAL(KREAL), ALLOCATABLE :: XyzTmp(:,:), XyzTmp2(:,:) ! (Nat,3)
62
  REAL(KREAL), ALLOCATABLE :: IntCoordTmp(:),DerInt(:) ! (NCoord)
63

    
64

    
65
  LOGICAL ::  debug, print
66
  LOGICAL, EXTERNAL :: valid
67

    
68
  !We will calculate the length of the path, in MW coordinates...
69
  ! this is done is a stupid way: we interpolate the zmatrix values,
70
  ! convert them into cartesian, weight the cartesian
71
  ! and calculate the evolution of the distance ! 
72
  ! We have to follow the same procedure for every geometry
73
  ! so even for the first one, we have to convert it from zmat
74
  ! to cartesian !
75

    
76
  debug=valid("pathcreate")
77
  print=valid("printgeom")
78

    
79
  if (debug) Call Header("Entering Extrapol_mixed")
80
  if (debug) WRITE(*,*) "NFroz,NCart",NFroz,NCart
81
  ALLOCATE(XyzTmp(Nat,3),XyzTmp2(Nat,3),IntCoordTmp(NCoord),DerInt(NCoord))
82
  IdxGeom=1
83
  
84
  IntCoordTmp=IntCoordI(1,1:NCoord)
85
  call Mixed2Cart(Nat,IndZmat,IntCoordTmp,XyzTmp2(1,1))
86

    
87
  XyzTmp=XyzTmp2
88

    
89
! We align this geometry with the original one
90
! PFL 01/feb/2007: useless when dealing with more than three cartesian atoms 
91
! PFL 17/July/2006: only if we have more than 4 atoms.
92
  IF ((NCart.LT.3).AND.(Nat.GT.4)) THEN
93
!  IF (Nat.GT.4) THEN
94
     Call  CalcRmsd(Nat, x0,y0,z0,                              &
95
          xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3),       &
96
          MRot,rmsd,FRot,FAlign)
97
  END IF
98

    
99
  XyzGeomF(IdxGeom,:,:)=Reshape(XyzTmp2(:,:),(/3,Nat/),ORDER=(/2,1/))
100
  IntCoordF(IdxGeom,:)=IntCoordI(1,:)
101

    
102
  if (print.AND.(Dist.LE.1e20)) THEN
103
     WRITE(IOOUT,'(1X,I5)') Nat
104
     WRITE(IOOUT,*) "# Cartesian Coordinates for geom",IdxGeom
105
     DO i=1,Nat
106
        If (Renum) THEN
107
           WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(I)),      &
108
                (XyzTmp2(Order(I),J),J=1,3)
109
        ELSE
110
           WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(OrderInv(I))),      &
111
                (XyzTmp2(I,J),J=1,3)
112
        END IF
113
     END DO
114
  END IF
115

    
116
! Calculate tangents for first geometry
117
  u=0.d0
118
     DO Idx=1,NCoord
119
           call splintder(u,IntCoordTmp(Idx),DerInt(Idx),NGeomI,xgeom(1),IntCoordI(1,Idx),Coef(1,Idx))
120
     END DO
121
     IntTangent(IdxGeom,:)=DerInt
122

    
123

    
124
! First geometry already initialized
125

    
126
  s=0.
127
!  valzmat=0.d0
128

    
129
  DO K=1,NMaxPtPath
130
     u=real(K)/NMaxPtPath*(NGeomI-1.)
131

    
132
     XYZTmp2=0.
133

    
134
! We generate the interpolated  coordinates
135
     DO Idx=1,NCoord
136
           call splintder(u,IntCoordTmp(Idx),DerInt(Idx),NGeomI,xgeom(1),IntCoordI(1,Idx),Coef(1,Idx))
137
     END DO
138

    
139
! We convert it into Cartesian coordinates
140
  call Mixed2Cart(Nat,IndZmat,IntCoordTmp,XyzTmp2(1,1))
141

    
142
! We calculate ds
143
     ds=0.
144
     DO I=1,Nat
145
        DO J=1,3
146
           ds=ds+MassAt(I)*(XYZTMp2(I,J)-XYZTmp(I,J))**2
147
           XYZTmp(I,J)=XyzTMP2(I,J)
148
        ENDDO
149
     ENDDO
150
     s=s+sqrt(ds)
151

    
152
!         if (debug) WRITE(*,*) "Debug u,s,dist",u,s,dist
153
     if (s>=dist) THEN
154
        s=s-dist
155
        IdxGeom=IdxGeom+1
156
        SGeom(IdxGeom)=s+IdxGeom*dist
157
        XyzGeomF(IdxGeom,:,:)=Reshape(XyzTmp2(:,:),(/3,Nat/),ORDER=(/2,1/))
158

    
159
        IntCoordF(IdxGeom,:)=IntCoordTmp
160
        IntTangent(IdxGeom,:)=DerInt
161

    
162
        if (print) THEN
163
           WRITE(IOOUT,'(1X,A,12(1X,F10.5))') "#Internal Coord",IntCoordTmp(1:NCoord)
164
           WRITE(IOOUT,'(1X,A,12(1X,F10.5))') "#Internal tan",IntTangent(IdxGeom,1:NCoord)
165
           WRITE(IOOUT,'(1X,I5)') Nat
166
           WRITE(IOOUT,*) "# Cartesian coord for Geometry ",IdxGeom,K,u,Xgeom(NGeomI)
167

    
168
! PFL 01/feb/2007: useless when dealing with more than three cartesian atoms 
169
! PFL 17/July/2006: only if we have more than 4 atoms.
170
           IF ((NCart.LT.3).AND.(Nat.GT.4)) THEN
171
!           IF (Nat.GT.4) THEN
172
              Call  CalcRmsd(Nat, x0,y0,z0,                               &
173
                   xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3),   &
174
                   MRot,rmsd,FRot,FAlign)
175
           END IF
176

    
177
           DO i=1,Nat
178
              If (Renum) THEN
179
                 WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(I)),   &
180
                      (XyzTmp2(Order(I),J),J=1,3)
181
              ELSE
182
                 WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(OrderInv(I))),    &
183
                      (XyzTmp2(I,J),J=1,3)
184
              END IF
185
           END DO
186

    
187
        END IF
188
     END IF
189
  END DO
190

    
191

    
192
  if ((s>=0.1*dist).AND.(IdxGeom.EQ.NGeomF)) THEN
193
     WRITE(*,*) "** PathCreate ***"
194
     WRITE(*,*) "Distribution of points along the path is wrong."
195
     WRITE(*,*) "Increase value of NMaxPtPath in the input file"
196
     WRITE(*,*) "Present value is:", NMaxPtPath
197
     STOP
198
  END IF
199

    
200
  IdxGeom=NGeomF
201

    
202
! We have to add the last geometry. We copy the last geom of Initial geometries.
203
  IntCoordF(IdxGeom,:)=IntCoordI(NGeomI,:)
204
  IntTangent(IdxGeom,:)=DerInt
205

    
206
! we convert it to cartesian geom
207
  call Mixed2Cart(Nat,IndZmat,IntCoordF(IdxGeom,1),XyzTmp2(1,1))
208
  XyzGeomF(IdxGeom,:,:)=Reshape(XyzTmp2(:,:),(/3,Nat/),ORDER=(/2,1/))
209

    
210
     if (print) THEN
211
        WRITE(IOOUT,'(1X,I5)') Nat
212
        WRITE(IOOUT,*) "# Cartesian coord for last Geometry ",IdxGeom,K,u,Xgeom(NGeomI)
213
! PFL 01/feb/2007: useless when dealing with more than three cartesian atoms 
214
! PFL 17/July/2006: only if we have more than 4 atoms.
215
        IF ((NCART.LT.3).AND.(Nat.GT.4)) THEN
216
!       IF (Nat.GT.4) THEN
217
           Call  CalcRmsd(Nat, x0,y0,z0,                          &
218
                xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3),    &
219
                MRot,rmsd,FRot,FAlign)
220
        END IF
221

    
222
        DO i=1,Nat
223
           If (Renum) THEN
224
              WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(I)),    &
225
                   (XyzTmp2(Order(I),J),J=1,3)
226
           ELSE
227
              WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(OrderInv(I))),     &
228
                   (XyzTmp2(I,J),J=1,3)
229
           END IF
230
        END DO
231
     END IF
232

    
233

    
234
  if (debug) WRITE(*,*) 's final =',s
235

    
236
  DEALLOCATE(XyzTmp,XyzTmp2)
237

    
238
  if (debug) Call Header("Extrapol_Mixed Over")
239

    
240
 
241
END SUBROUTINE EXTRAPOL_MIXED