Statistiques
| Révision :

root / src / Extrapol_baker.f90 @ 12

Historique | Voir | Annoter | Télécharger (11,89 ko)

1 1 pfleura2
SUBROUTINE Extrapol_baker(s,dist,x0,y0,z0,xgeom,Coef,XgeomF)
2 1 pfleura2
3 1 pfleura2
  ! This subroutine constructs the path, andabscissa if dist<>Infinity, it samples
4 1 pfleura2
  ! the path to obtain geometries.
5 1 pfleura2
  ! Basically, you call it twice: i) dist=infinity, it will calculate the length of the path
6 1 pfleura2
  ! ii) dist finite, it will give you the images you want along the path.
7 1 pfleura2
  !
8 1 pfleura2
  ! For now, it gives equidistant geometries.
9 1 pfleura2
  !
10 1 pfleura2
  ! A reference geometry for the alignment: X0(Nat),Y0(Nat),Z0(Nat)
11 1 pfleura2
12 12 pfleura2
!----------------------------------------------------------------------
13 12 pfleura2
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon,
14 12 pfleura2
!  Centre National de la Recherche Scientifique,
15 12 pfleura2
!  Université Claude Bernard Lyon 1. All rights reserved.
16 12 pfleura2
!
17 12 pfleura2
!  This work is registered with the Agency for the Protection of Programs
18 12 pfleura2
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
19 12 pfleura2
!
20 12 pfleura2
!  Authors: P. Fleurat-Lessard, P. Dayal
21 12 pfleura2
!  Contact: optnpath@gmail.com
22 12 pfleura2
!
23 12 pfleura2
! This file is part of "Opt'n Path".
24 12 pfleura2
!
25 12 pfleura2
!  "Opt'n Path" is free software: you can redistribute it and/or modify
26 12 pfleura2
!  it under the terms of the GNU Affero General Public License as
27 12 pfleura2
!  published by the Free Software Foundation, either version 3 of the License,
28 12 pfleura2
!  or (at your option) any later version.
29 12 pfleura2
!
30 12 pfleura2
!  "Opt'n Path" is distributed in the hope that it will be useful,
31 12 pfleura2
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
32 12 pfleura2
!
33 12 pfleura2
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
34 12 pfleura2
!  GNU Affero General Public License for more details.
35 12 pfleura2
!
36 12 pfleura2
!  You should have received a copy of the GNU Affero General Public License
37 12 pfleura2
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
38 12 pfleura2
!
39 12 pfleura2
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
40 12 pfleura2
! for commercial licensing opportunities.
41 12 pfleura2
!----------------------------------------------------------------------
42 12 pfleura2
43 1 pfleura2
  use Path_module, only : IntCoordI, NMaxPtPath, XyzGeomF, IntCoordF, &
44 1 pfleura2
       IntTangent, Renum, Nom, Order, MassAt, SGeom, Nat, NGeomI, &
45 1 pfleura2
       NGeomF, Atome, NCoord, OrderInv, XyzGeomI,BTransInvF, &
46 1 pfleura2
       XPrimitive,XPrimitiveF, NPrim,                                      &
47 1 pfleura2
       BTransInv_local,UMatF,UMat_local,FirstTimePathCreate,Pi
48 1 pfleura2
  ! IntCoordI(NGeomI,3*Nat-6), Coef(NGeomI,NCoord), NMaxPtPath=1000 (default value)
49 1 pfleura2
  ! More appropriate: IntCoordI(NGeomI,NCoord)
50 1 pfleura2
  use Io_module
51 1 pfleura2
  IMPLICIT NONE
52 1 pfleura2
53 1 pfleura2
  REAL(KREAL), INTENT(OUT) :: s
54 1 pfleura2
  ! A reference geometry for the alignment:
55 1 pfleura2
  REAL(KREAL), INTENT(IN) :: dist,X0(Nat),Y0(Nat),Z0(Nat)
56 1 pfleura2
  ! Xgeom(NGeomI): abscissa of all initial geometries.
57 1 pfleura2
  ! Coef(NGeomI,NCoord): spline coefficients.
58 1 pfleura2
  REAL(KREAL), INTENT(IN) :: Xgeom(NGeomI),Coef(NGeomI,NCoord)
59 1 pfleura2
  ! Number of the cycles for the optimization:
60 1 pfleura2
  ! XGeomF(NGeomF): Final geometries.
61 1 pfleura2
  REAL(KREAL), INTENT(OUT) :: XGeomF(NGeomF)
62 1 pfleura2
63 2 pfleura2
  INTEGER(KINT) :: IdxGeom, I, J, K
64 1 pfleura2
  REAL(KREAL) :: Rmsd,MRot(3,3), ds, u, v
65 1 pfleura2
66 1 pfleura2
  REAL(KREAL), ALLOCATABLE :: XyzTmp(:,:), XyzTmp2(:,:), DerInt(:) ! (Nat,3)
67 1 pfleura2
  REAL(KREAL), ALLOCATABLE :: Xyz_k(:,:) ! (Nat,3)
68 1 pfleura2
  REAL(KREAL), ALLOCATABLE :: IntCoord_interpol(:) ! (3*Nat-6)
69 1 pfleura2
  REAL(KREAL), ALLOCATABLE :: IntCoord_k(:) ! (3*Nat-6)
70 1 pfleura2
  REAL(KREAL), ALLOCATABLE :: XPrimRef(:),XPrim(:) ! NPrim
71 1 pfleura2
72 1 pfleura2
  LOGICAL ::  debug, print,printspline
73 1 pfleura2
  LOGICAL, EXTERNAL :: valid
74 1 pfleura2
75 1 pfleura2
  INTEGER(KINT) :: NSpline
76 1 pfleura2
77 1 pfleura2
78 1 pfleura2
  ! We will calculate the length of the path, in MW coordinates...
79 1 pfleura2
  ! this is done in a stupid way: we interpolate the Baker coordinates values,
80 1 pfleura2
  ! convert them into cartesian, weight the cartesian
81 1 pfleura2
  ! and calculate the evolution of the distance !
82 1 pfleura2
  ! We have to follow the same procedure for every geometry,
83 1 pfleura2
  ! so even for the first one, we have to convert it from internal Baker
84 1 pfleura2
  ! coordinates to cartesian !
85 1 pfleura2
86 1 pfleura2
  debug=valid("Extrapol_baker")
87 1 pfleura2
  print=valid("printgeom")
88 1 pfleura2
  printspline=(valid("printspline").AND.(dist<=1e30))
89 1 pfleura2
90 1 pfleura2
  if (debug) WRITE(*,*) "================= Entering Extrapol_baker ===================="
91 1 pfleura2
  if (debug) WRITE(*,*) "DBG Extrapol_baker dist=",Dist
92 1 pfleura2
  NSpline=int(NMaxPtPath/100)
93 1 pfleura2
  !IF (printspline) THEN
94 1 pfleura2
  !  WRITE(TmpChar,'(I5)') Iopt
95 1 pfleura2
  ! FileSpline=Trim(adjustL(PathName)) // '_spline.' // AdjustL(TRIM(TmpChar))
96 1 pfleura2
  !OPEN(IOTMP,FILE=FileSpline)
97 1 pfleura2
  ! END IF
98 1 pfleura2
99 1 pfleura2
  ALLOCATE(XyzTmp(Nat,3),XyzTmp2(Nat,3),IntCoord_interpol(NCoord),DerInt(NCoord))
100 1 pfleura2
  ALLOCATE(IntCoord_k(NCoord),Xyz_k(Nat,3))
101 1 pfleura2
  ALLOCATE(XPrimRef(NPrim),XPrim(NPrim))
102 1 pfleura2
103 1 pfleura2
  ! XyzGeomI(:,:,:) ! (NGeomI,3,Nat)
104 1 pfleura2
  ! IntCoordI(:,:) ! (NGeomI,3*Nat-6)
105 1 pfleura2
106 1 pfleura2
  !XyzGeomF(1,:,:)=Reshape(XyzTmp2(:,:),(/3,Nat/),ORDER=(/2,1/))
107 1 pfleura2
  XyzGeomF(1,:,:)=XyzGeomI(1,:,:) ! 1st index is geometry-index.
108 1 pfleura2
  IntCoordF(1,:)=IntCoordI(1,:)
109 1 pfleura2
110 1 pfleura2
  ! We calculate the first derivatives
111 1 pfleura2
  u=0.d0
112 1 pfleura2
  DO I=1,NCoord
113 1 pfleura2
     ! Given the arrays xgeom(1:NGeomI) and IntCoordI(1:NGeomI,Idx) of length
114 1 pfleura2
     ! NGeomI, which tabulate a function
115 1 pfleura2
     ! (with the xgeom's in order), and given the array Coef(1:NGeomI,Idx),
116 1 pfleura2
     ! which is the output from spline, and given a value of u,
117 1 pfleura2
     ! this routine returns a cubic-spline interpolated value v.
118 1 pfleura2
     ! and the derivative DerInt(Idx).
119 1 pfleura2
     call splintder(u,v,DerInt(I),NGeomI,xgeom(1),IntCoordI(1,I),Coef(1,I))
120 1 pfleura2
  END DO
121 1 pfleura2
  IntTangent(1,:)=DerInt
122 1 pfleura2
123 1 pfleura2
  IF (print.AND.(Dist.LE.1e20)) THEN
124 1 pfleura2
     WRITE(IOOUT,'(1X,I5)') Nat
125 1 pfleura2
     WRITE(IOOUT,*) "# Cartesian Coordinates for geom",1
126 1 pfleura2
     DO I=1,Nat
127 1 pfleura2
        If (Renum) THEN
128 1 pfleura2
           WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(I)), &
129 1 pfleura2
                (XyzTmp2(Order(I),J),J=1,3)
130 1 pfleura2
        ELSE
131 1 pfleura2
           WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(OrderInv(I))), &
132 1 pfleura2
                (XyzTmp2(I,J),J=1,3)
133 1 pfleura2
        END IF
134 1 pfleura2
     END DO
135 1 pfleura2
  END IF ! matches IF (print.AND.(Dist.LE.1e20)) THEN
136 1 pfleura2
137 1 pfleura2
  XyzTmp(:,1) = XyzGeomI(1,1,:) ! 1st index is geometry-index.
138 1 pfleura2
  XyzTmp(:,2) = XyzGeomI(1,2,:)
139 1 pfleura2
  XyzTmp(:,3) = XyzGeomI(1,3,:)
140 1 pfleura2
141 1 pfleura2
  s=0.d0
142 1 pfleura2
  IntCoord_k=IntCoordF(1,:)
143 1 pfleura2
  Xyz_k(:,1) = XyzGeomI(1,1,:) ! 1st index is geometry-index.
144 1 pfleura2
  Xyz_k(:,2) = XyzGeomI(1,2,:)
145 1 pfleura2
  Xyz_k(:,3) = XyzGeomI(1,3,:)
146 1 pfleura2
  IdxGeom=1
147 1 pfleura2
  XPrimRef=XPrimitive(1,:)
148 1 pfleura2
  XPrimitiveF(1,:)=XPrimitive(1,:)
149 1 pfleura2
  DO K=1,NMaxPtPath
150 1 pfleura2
     u=real(K)/NMaxPtPath*(NGeomI-1.)
151 1 pfleura2
152 1 pfleura2
     ! We generate the interpolated internal coordinates in v.
153 1 pfleura2
     ! Given the arrays Xgeom(1:NGeomI) (Xgeom(NGeomI): abscissa of all initial geometries)
154 1 pfleura2
     ! and IntCoordI(1:NGeomI,I) of length NGeomI, which tabulate a function (with the
155 1 pfleura2
     ! Xgeom's in order), and given the array Coef(1:NGeomI,Idx), which is the output from
156 1 pfleura2
     ! spline, and given a value of u, this routine returns a cubic-spline interpolated
157 1 pfleura2
     ! value v and the derivative DerInt(I).
158 1 pfleura2
159 1 pfleura2
     ! this loop is to be confirmed:
160 1 pfleura2
     ! IntCoordI(NGeomI,3*Nat-6)
161 1 pfleura2
     DO I=1,NCoord
162 1 pfleura2
        call splintder(u,v,DerInt(I),NGeomI,Xgeom(1),IntCoordI(1,I),Coef(1,I))
163 1 pfleura2
        IntCoord_interpol(I)=v
164 1 pfleura2
     END DO
165 1 pfleura2
     IF(.NOT.FirstTimePathCreate) Then
166 1 pfleura2
       WRITE(*,*) "DBG Extrapol_baker Umat_local=UMatF"
167 1 pfleura2
        DO I=1,NCoord ! these variables are used in ConvertBakerInternal_cart()
168 1 pfleura2
           BTransInv_local(I,:) = BTransInvF(IdxGeom,I,:)
169 1 pfleura2
           UMat_local(:,I) = UMatF(IdxGeom,:,I)
170 1 pfleura2
        END DO
171 1 pfleura2
     END IF
172 1 pfleura2
     ! We convert it into Cartesian coordinates:
173 1 pfleura2
     if (debug) WRITE(*,*) "DBG Extrapol_baker, call ConvertBakerInt_car for k=",k
174 1 pfleura2
     Call ConvertBakerInternal_cart(IntCoord_k,IntCoord_interpol,Xyz_k(1,1), &
175 1 pfleura2
          Xyz_k(1,2),Xyz_k(1,3),XyzTMP2(1,1),XyzTMP2(1,2),XyzTMP2(1,3),XPrim,XPrimRef)
176 1 pfleura2
     XPrimRef=Xprim
177 1 pfleura2
     IF(.NOT.FirstTimePathCreate) Then
178 1 pfleura2
        DO I=1,NCoord ! these variables are used in ConvertBakerInternal_cart()
179 1 pfleura2
           BTransInvF(IdxGeom,I,:) = BTransInv_local(I,:)
180 1 pfleura2
        END DO
181 1 pfleura2
     END IF
182 1 pfleura2
183 1 pfleura2
     if (debug) THEN
184 1 pfleura2
        WRITE(*,*) "DBG Extrapol_baker, XyzTmp2 before RMSD"
185 1 pfleura2
           DO I=1,Nat
186 1 pfleura2
              IF (Renum) THEN
187 1 pfleura2
                 WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(I)), &
188 1 pfleura2
                      (XyzTmp2(Order(I),J),J=1,3)
189 1 pfleura2
              ELSE
190 1 pfleura2
                 WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(OrderInv(I))), &
191 1 pfleura2
                      (XyzTmp2(I,J),J=1,3)
192 1 pfleura2
              END IF
193 1 pfleura2
           END DO
194 1 pfleura2
        END IF
195 1 pfleura2
196 1 pfleura2
197 1 pfleura2
     call CalcRmsd(Nat,XyzTmp(1:Nat,1),XyzTmp(1:Nat,2),XyzTmp(1:Nat,3), &
198 1 pfleura2
    XyzTmp2(1:Nat,1),XyzTmp2(1:Nat,2),XyzTmp2(1:Nat,3),           &
199 1 pfleura2
          MRot,rmsd,.TRUE.,.TRUE.)
200 1 pfleura2
201 1 pfleura2
202 1 pfleura2
     if (debug) THEN
203 1 pfleura2
        WRITE(*,*) "DBG Extrapol_baker, XyzTmp2 after RMSD"
204 1 pfleura2
           DO I=1,Nat
205 1 pfleura2
              IF (Renum) THEN
206 1 pfleura2
                 WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(I)), &
207 1 pfleura2
                      (XyzTmp2(Order(I),J),J=1,3)
208 1 pfleura2
              ELSE
209 1 pfleura2
                 WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(OrderInv(I))), &
210 1 pfleura2
                      (XyzTmp2(I,J),J=1,3)
211 1 pfleura2
              END IF
212 1 pfleura2
           END DO
213 1 pfleura2
        END IF
214 1 pfleura2
215 1 pfleura2
216 1 pfleura2
     IntCoord_k=IntCoord_interpol
217 1 pfleura2
     Xyz_k(:,1)=XyzTMP2(:,1)
218 1 pfleura2
     Xyz_k(:,2)=XyzTMP2(:,2)
219 1 pfleura2
     Xyz_k(:,3)=XyzTMP2(:,3)
220 1 pfleura2
221 1 pfleura2
     ds=0.
222 1 pfleura2
     DO I=1,Nat
223 1 pfleura2
        DO J=1,3
224 1 pfleura2
           ds=ds+MassAt(I)*(XYZTMp2(I,J)-XYZTmp(I,J))**2
225 1 pfleura2
           XYZTmp(I,J)=XyzTMP2(I,J)
226 1 pfleura2
        END DO
227 1 pfleura2
     END DO
228 1 pfleura2
229 1 pfleura2
     s=s+sqrt(ds)
230 1 pfleura2
231 1 pfleura2
     IF (s>=dist) THEN
232 1 pfleura2
        if (debug) THEN
233 1 pfleura2
           WRITE(*,*) "DBG Extrapol_baker s,IdxGeom,dist",s,IdxGeom,dist
234 1 pfleura2
           WRITE(*,'(50(1X,F12.8))') IntCoord_interpol
235 1 pfleura2
           WRITE(*,*) "DBG Extrapol_baker Angles in deg ?"
236 1 pfleura2
           WRITE(*,'(50(1X,F12.8))') IntCoord_interpol*180./pi
237 1 pfleura2
        END IF
238 1 pfleura2
        s=s-dist
239 1 pfleura2
        IdxGeom=IdxGeom+1
240 1 pfleura2
        XprimitiveF(IdxGeom,:)=Xprim(:)
241 1 pfleura2
        UMatF(IdxGeom,:,:)=UMat_local(:,:)
242 1 pfleura2
        SGeom(IdxGeom)=s+IdxGeom*dist !SGeom(NGeomF)
243 1 pfleura2
        XgeomF(IdxGeom)=u
244 1 pfleura2
        XyzGeomF(IdxGeom,:,:)=Reshape(XyzTmp2(:,:),(/3,Nat/),ORDER=(/2,1/))
245 1 pfleura2
246 1 pfleura2
        ! IntCoordF(NGeomF,NCoord): Final Internal coordinates for number of final
247 1 pfleura2
        ! geometries. NCoord is the number of coordinates (NCoord) of each geometry.
248 1 pfleura2
        IntCoordF(IdxGeom,:)=IntCoord_interpol(:)
249 1 pfleura2
        IntTangent(IdxGeom,:)=DerInt
250 1 pfleura2
251 1 pfleura2
        IF (print) THEN
252 1 pfleura2
           WRITE(IOOUT,'(1X,I5)') Nat
253 1 pfleura2
           WRITE(IOOUT,*) "# Cartesian coord for Geometry ",IdxGeom,K
254 1 pfleura2
           ! PFL 17/July/2006: only if we have more than 4 atoms.
255 1 pfleura2
           IF (Nat.GE.4) THEN
256 1 pfleura2
              Call  CalcRmsd(Nat,x0,y0,z0, &
257 1 pfleura2
                   xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3), &
258 1 pfleura2
                   MRot,rmsd,.TRUE.,.TRUE.)
259 1 pfleura2
           END IF
260 1 pfleura2
261 1 pfleura2
           DO I=1,Nat
262 1 pfleura2
              IF (Renum) THEN
263 1 pfleura2
                 WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(I)), &
264 1 pfleura2
                      (XyzTmp2(Order(I),J),J=1,3)
265 1 pfleura2
              ELSE
266 1 pfleura2
                 WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(OrderInv(I))), &
267 1 pfleura2
                      (XyzTmp2(I,J),J=1,3)
268 1 pfleura2
              END IF
269 1 pfleura2
           END DO
270 1 pfleura2
        END IF !matches IF (print) THEN
271 1 pfleura2
     END IF ! matches IF (s>=dist) THEN
272 1 pfleura2
  END DO ! matches DO K=1,NMaxPtPath
273 1 pfleura2
274 1 pfleura2
275 1 pfleura2
  if (s>=0.9*dist) THEN
276 1 pfleura2
     s=s-dist
277 1 pfleura2
     IdxGeom=IdxGeom+1
278 1 pfleura2
     SGeom(IdxGeom)=s+IdxGeom*dist
279 1 pfleura2
     XgeomF(IdxGeom)=min(u,NGeomI-1.d0)
280 1 pfleura2
     XyzGeomF(IdxGeom,:,:)=Reshape(XyzTmp2(:,:),(/3,Nat/),ORDER=(/2,1/))
281 1 pfleura2
     !  XyzGeomF(IdxGeom,:,:)=XyzTmp2(:,:)
282 1 pfleura2
283 1 pfleura2
     IntCoordF(IdxGeom,:)=IntCoord_interpol(:)
284 1 pfleura2
     XprimitiveF(IdxGeom,:)=Xprim(:)
285 1 pfleura2
     UMatF(IdxGeom,:,:)=UMat_local(:,:)
286 1 pfleura2
     IntTangent(IdxGeom,:)=DerInt
287 1 pfleura2
288 1 pfleura2
     if (print) THEN
289 1 pfleura2
        WRITE(IOOUT,'(1X,I5)') Nat
290 1 pfleura2
        WRITE(IOOUT,*) "# Cartesian coord for Geometry ",IdxGeom,K
291 1 pfleura2
        ! PFL 17/July/2006: only if we have more than 4 atoms.
292 1 pfleura2
        IF (Nat.GE.4) THEN
293 1 pfleura2
           Call  CalcRmsd(Nat,x0,y0,z0, &
294 1 pfleura2
                xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3), &
295 1 pfleura2
                MRot,rmsd,.TRUE.,.TRUE.)
296 1 pfleura2
        END IF
297 1 pfleura2
298 1 pfleura2
        DO I=1,Nat
299 1 pfleura2
           IF (Renum) THEN
300 1 pfleura2
              WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(I)), &
301 1 pfleura2
                   (XyzTmp2(Order(I),J),J=1,3)
302 1 pfleura2
           ELSE
303 1 pfleura2
              WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(OrderInv(I))), &
304 1 pfleura2
                   (XyzTmp2(I,J),J=1,3)
305 1 pfleura2
           END IF
306 1 pfleura2
        END DO
307 1 pfleura2
     END IF ! matches if (print) THEN
308 1 pfleura2
  END IF ! matches if (s>=0.9*dist) THEN
309 1 pfleura2
310 1 pfleura2
  if (debug) WRITE(*,*) 's final =',s
311 1 pfleura2
   if (debug) THEN
312 1 pfleura2
      WRITE(*,*) "XPrimitiveF"
313 1 pfleura2
      DO I=1,NGeomF
314 1 pfleura2
        WRITE(*,'(1X,I5," : ",50(1X,F10.6))') I,XPrimitiveF(I,:)
315 1 pfleura2
     END DO
316 1 pfleura2
     END IF
317 1 pfleura2
318 1 pfleura2
  DEALLOCATE(XyzTmp,XyzTmp2,IntCoord_interpol,IntCoord_k,Xyz_k)
319 1 pfleura2
320 1 pfleura2
  if (printspline) CLOSE(IOTMP)
321 1 pfleura2
  if (debug) WRITE(*,*) "================= Extrapol_baker Over ====================="
322 1 pfleura2
323 1 pfleura2
END SUBROUTINE EXTRAPOL_BAKER