Statistiques
| Révision :

root / src / Extrapol_mixed.f90 @ 1

Historique | Voir | Annoter | Télécharger (6,41 ko)

1 1 pfleura2
SUBROUTINE Extrapol_mixed(s,dist,x0,y0,z0,xgeom,Coef)
2 1 pfleura2
3 1 pfleura2
! This subroutine constructs the path, and 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
6 1 pfleura2
! length of the path
7 1 pfleura2
! ii) dist finite, it will give you the images you want along the path.
8 1 pfleura2
!
9 1 pfleura2
! For now, it gives equidistant geometries
10 1 pfleura2
!!!!!!!!!!!!!!!!
11 1 pfleura2
!
12 1 pfleura2
! v2.0
13 1 pfleura2
! Uses Mix2cart for conversions.
14 1 pfleura2
15 1 pfleura2
16 1 pfleura2
  use Path_module
17 1 pfleura2
  use Io_module
18 1 pfleura2
19 1 pfleura2
20 1 pfleura2
  IMPLICIT NONE
21 1 pfleura2
22 1 pfleura2
23 1 pfleura2
  REAL(KREAL), INTENT(OUT) :: s
24 1 pfleura2
  REAL(KREAL), INTENT(IN) :: dist,X0(Nat),Y0(Nat),Z0(Nat)
25 1 pfleura2
  REAL(KREAL), INTENT(IN) :: Xgeom(NGeomI),Coef(NGeomI,NCoord)
26 1 pfleura2
27 1 pfleura2
  INTEGER(KINT) :: IdxGeom, I, J, K, Idx
28 1 pfleura2
  REAL(KREAL) :: Rmsd,MRot(3,3), ds, u, v
29 1 pfleura2
  REAL(KREAL) :: a_val, d
30 1 pfleura2
31 1 pfleura2
  REAL(KREAL), ALLOCATABLE :: XyzTmp(:,:), XyzTmp2(:,:) ! (Nat,3)
32 1 pfleura2
  REAL(KREAL), ALLOCATABLE :: IntCoordTmp(:),DerInt(:) ! (NCoord)
33 1 pfleura2
34 1 pfleura2
35 1 pfleura2
  LOGICAL ::  debug, print
36 1 pfleura2
  LOGICAL, EXTERNAL :: valid
37 1 pfleura2
38 1 pfleura2
  !We will calculate the length of the path, in MW coordinates...
39 1 pfleura2
  ! this is done is a stupid way: we interpolate the zmatrix values,
40 1 pfleura2
  ! convert them into cartesian, weight the cartesian
41 1 pfleura2
  ! and calculate the evolution of the distance !
42 1 pfleura2
  ! We have to follow the same procedure for every geometry
43 1 pfleura2
  ! so even for the first one, we have to convert it from zmat
44 1 pfleura2
  ! to cartesian !
45 1 pfleura2
46 1 pfleura2
  debug=valid("pathcreate")
47 1 pfleura2
  print=valid("printgeom")
48 1 pfleura2
49 1 pfleura2
  if (debug) Call Header("Entering Extrapol_mixed")
50 1 pfleura2
  if (debug) WRITE(*,*) "NFroz,NCart",NFroz,NCart
51 1 pfleura2
  ALLOCATE(XyzTmp(Nat,3),XyzTmp2(Nat,3),IntCoordTmp(NCoord),DerInt(NCoord))
52 1 pfleura2
  IdxGeom=1
53 1 pfleura2
54 1 pfleura2
  IntCoordTmp=IntCoordI(1,1:NCoord)
55 1 pfleura2
  call Mixed2Cart(Nat,IndZmat,IntCoordTmp,XyzTmp2(1,1))
56 1 pfleura2
57 1 pfleura2
  XyzTmp=XyzTmp2
58 1 pfleura2
59 1 pfleura2
! We align this geometry with the original one
60 1 pfleura2
! PFL 01/feb/2007: useless when dealing with more than three cartesian atoms
61 1 pfleura2
! PFL 17/July/2006: only if we have more than 4 atoms.
62 1 pfleura2
  IF ((NCart.LT.3).AND.(Nat.GT.4)) THEN
63 1 pfleura2
!  IF (Nat.GT.4) THEN
64 1 pfleura2
     Call  CalcRmsd(Nat, x0,y0,z0,                              &
65 1 pfleura2
          xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3),       &
66 1 pfleura2
          MRot,rmsd,FRot,FAlign)
67 1 pfleura2
  END IF
68 1 pfleura2
69 1 pfleura2
  XyzGeomF(IdxGeom,:,:)=Reshape(XyzTmp2(:,:),(/3,Nat/),ORDER=(/2,1/))
70 1 pfleura2
  IntCoordF(IdxGeom,:)=IntCoordI(1,:)
71 1 pfleura2
72 1 pfleura2
  if (print.AND.(Dist.LE.1e20)) THEN
73 1 pfleura2
     WRITE(IOOUT,'(1X,I5)') Nat
74 1 pfleura2
     WRITE(IOOUT,*) "# Cartesian Coordinates for geom",IdxGeom
75 1 pfleura2
     DO i=1,Nat
76 1 pfleura2
        If (Renum) THEN
77 1 pfleura2
           WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(I)),      &
78 1 pfleura2
                (XyzTmp2(Order(I),J),J=1,3)
79 1 pfleura2
        ELSE
80 1 pfleura2
           WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(OrderInv(I))),      &
81 1 pfleura2
                (XyzTmp2(I,J),J=1,3)
82 1 pfleura2
        END IF
83 1 pfleura2
     END DO
84 1 pfleura2
  END IF
85 1 pfleura2
86 1 pfleura2
! Calculate tangents for first geometry
87 1 pfleura2
  u=0.d0
88 1 pfleura2
     DO Idx=1,NCoord
89 1 pfleura2
           call splintder(u,IntCoordTmp(Idx),DerInt(Idx),NGeomI,xgeom(1),IntCoordI(1,Idx),Coef(1,Idx))
90 1 pfleura2
     END DO
91 1 pfleura2
     IntTangent(IdxGeom,:)=DerInt
92 1 pfleura2
93 1 pfleura2
94 1 pfleura2
! First geometry already initialized
95 1 pfleura2
96 1 pfleura2
  s=0.
97 1 pfleura2
!  valzmat=0.d0
98 1 pfleura2
99 1 pfleura2
  DO K=1,NMaxPtPath
100 1 pfleura2
     u=real(K)/NMaxPtPath*(NGeomI-1.)
101 1 pfleura2
102 1 pfleura2
     XYZTmp2=0.
103 1 pfleura2
104 1 pfleura2
! We generate the interpolated  coordinates
105 1 pfleura2
     DO Idx=1,NCoord
106 1 pfleura2
           call splintder(u,IntCoordTmp(Idx),DerInt(Idx),NGeomI,xgeom(1),IntCoordI(1,Idx),Coef(1,Idx))
107 1 pfleura2
     END DO
108 1 pfleura2
109 1 pfleura2
! We convert it into Cartesian coordinates
110 1 pfleura2
  call Mixed2Cart(Nat,IndZmat,IntCoordTmp,XyzTmp2(1,1))
111 1 pfleura2
112 1 pfleura2
! We calculate ds
113 1 pfleura2
     ds=0.
114 1 pfleura2
     DO I=1,Nat
115 1 pfleura2
        DO J=1,3
116 1 pfleura2
           ds=ds+MassAt(I)*(XYZTMp2(I,J)-XYZTmp(I,J))**2
117 1 pfleura2
           XYZTmp(I,J)=XyzTMP2(I,J)
118 1 pfleura2
        ENDDO
119 1 pfleura2
     ENDDO
120 1 pfleura2
     s=s+sqrt(ds)
121 1 pfleura2
122 1 pfleura2
!         if (debug) WRITE(*,*) "Debug u,s,dist",u,s,dist
123 1 pfleura2
     if (s>=dist) THEN
124 1 pfleura2
        s=s-dist
125 1 pfleura2
        IdxGeom=IdxGeom+1
126 1 pfleura2
        XyzGeomF(IdxGeom,:,:)=Reshape(XyzTmp2(:,:),(/3,Nat/),ORDER=(/2,1/))
127 1 pfleura2
128 1 pfleura2
        IntCoordF(IdxGeom,:)=IntCoordTmp
129 1 pfleura2
        IntTangent(IdxGeom,:)=DerInt
130 1 pfleura2
131 1 pfleura2
        if (print) THEN
132 1 pfleura2
           WRITE(IOOUT,'(1X,A,12(1X,F10.5))') "#Internal Coord",IntCoordTmp(1:NCoord)
133 1 pfleura2
           WRITE(IOOUT,'(1X,A,12(1X,F10.5))') "#Internal tan",IntTangent(IdxGeom,1:NCoord)
134 1 pfleura2
           WRITE(IOOUT,'(1X,I5)') Nat
135 1 pfleura2
           WRITE(IOOUT,*) "# Cartesian coord for Geometry ",IdxGeom,K,u,Xgeom(NGeomI)
136 1 pfleura2
137 1 pfleura2
! PFL 01/feb/2007: useless when dealing with more than three cartesian atoms
138 1 pfleura2
! PFL 17/July/2006: only if we have more than 4 atoms.
139 1 pfleura2
           IF ((NCart.LT.3).AND.(Nat.GT.4)) THEN
140 1 pfleura2
!           IF (Nat.GT.4) THEN
141 1 pfleura2
              Call  CalcRmsd(Nat, x0,y0,z0,                               &
142 1 pfleura2
                   xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3),   &
143 1 pfleura2
                   MRot,rmsd,FRot,FAlign)
144 1 pfleura2
           END IF
145 1 pfleura2
146 1 pfleura2
           DO i=1,Nat
147 1 pfleura2
              If (Renum) THEN
148 1 pfleura2
                 WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(I)),   &
149 1 pfleura2
                      (XyzTmp2(Order(I),J),J=1,3)
150 1 pfleura2
              ELSE
151 1 pfleura2
                 WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(OrderInv(I))),    &
152 1 pfleura2
                      (XyzTmp2(I,J),J=1,3)
153 1 pfleura2
              END IF
154 1 pfleura2
           END DO
155 1 pfleura2
156 1 pfleura2
        END IF
157 1 pfleura2
     END IF
158 1 pfleura2
  ENDDO
159 1 pfleura2
160 1 pfleura2
161 1 pfleura2
  if ((s>=0.1*dist).AND.(IdxGeom.EQ.NGeomF)) THEN
162 1 pfleura2
     WRITE(*,*) "** PathCreate ***"
163 1 pfleura2
     WRITE(*,*) "Distribution of points along the path is wrong."
164 1 pfleura2
     WRITE(*,*) "Increase value of NMaxPtPath in the input file"
165 1 pfleura2
     WRITE(*,*) "Present value is:", NMaxPtPath
166 1 pfleura2
     STOP
167 1 pfleura2
  END IF
168 1 pfleura2
169 1 pfleura2
  IdxGeom=NGeomF
170 1 pfleura2
171 1 pfleura2
! We have to add the last geometry. We copy the last geom of Initial geometries.
172 1 pfleura2
     IntCoordF(IdxGeom,:)=IntCoordI(NGeomI,:)
173 1 pfleura2
     IntTangent(IdxGeom,:)=DerInt
174 1 pfleura2
175 1 pfleura2
! we convert it to cartesian geom
176 1 pfleura2
  call Mixed2Cart(Nat,IndZmat,IntCoordF(IdxGeom,1),XyzTmp2(1,1))
177 1 pfleura2
  XyzGeomF(IdxGeom,:,:)=Reshape(XyzTmp2(:,:),(/3,Nat/),ORDER=(/2,1/))
178 1 pfleura2
179 1 pfleura2
     if (print) THEN
180 1 pfleura2
        WRITE(IOOUT,'(1X,I5)') Nat
181 1 pfleura2
        WRITE(IOOUT,*) "# Cartesian coord for last Geometry ",IdxGeom,K,u,Xgeom(NGeomI)
182 1 pfleura2
! PFL 01/feb/2007: useless when dealing with more than three cartesian atoms
183 1 pfleura2
! PFL 17/July/2006: only if we have more than 4 atoms.
184 1 pfleura2
        IF ((NCART.LT.3).AND.(Nat.GT.4)) THEN
185 1 pfleura2
!       IF (Nat.GT.4) THEN
186 1 pfleura2
           Call  CalcRmsd(Nat, x0,y0,z0,                          &
187 1 pfleura2
                xyzTmp2(1,1),xyzTmp2(1,2),xyzTMP2(1,3),    &
188 1 pfleura2
                MRot,rmsd,FRot,FAlign)
189 1 pfleura2
        END IF
190 1 pfleura2
191 1 pfleura2
        DO i=1,Nat
192 1 pfleura2
           If (Renum) THEN
193 1 pfleura2
              WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(I)),    &
194 1 pfleura2
                   (XyzTmp2(Order(I),J),J=1,3)
195 1 pfleura2
           ELSE
196 1 pfleura2
              WRITE(IOOUT,'(1X,A2,3(1X,F15.6))') Nom(Atome(OrderInv(I))),     &
197 1 pfleura2
                   (XyzTmp2(I,J),J=1,3)
198 1 pfleura2
           END IF
199 1 pfleura2
        END DO
200 1 pfleura2
     END IF
201 1 pfleura2
202 1 pfleura2
203 1 pfleura2
  if (debug) WRITE(*,*) 's final =',s
204 1 pfleura2
205 1 pfleura2
  DEALLOCATE(XyzTmp,XyzTmp2)
206 1 pfleura2
207 1 pfleura2
  if (debug) Call Header("Extrapol_Mixed Over")
208 1 pfleura2
209 1 pfleura2
210 1 pfleura2
END SUBROUTINE EXTRAPOL_MIXED