root / src / AnaPath.f90
Historique | Voir | Annoter | Télécharger (7,33 ko)
1 |
!================================================================ |
---|---|
2 |
! |
3 |
! This subroutine analyzes the geometries along a path |
4 |
! and prints it to FileUnit |
5 |
!================================================================ |
6 |
|
7 |
SUBROUTINE AnaPath(IOpt,FileUnit) |
8 |
|
9 |
!---------------------------------------------------------------------- |
10 |
! Copyright 2003-2014 Ecole Normale Supérieure de Lyon, |
11 |
! Centre National de la Recherche Scientifique, |
12 |
! Université Claude Bernard Lyon 1. All rights reserved. |
13 |
! |
14 |
! This work is registered with the Agency for the Protection of Programs |
15 |
! as IDDN.FR.001.100009.000.S.P.2014.000.30625 |
16 |
! |
17 |
! Authors: P. Fleurat-Lessard, P. Dayal |
18 |
! Contact: optnpath@gmail.com |
19 |
! |
20 |
! This file is part of "Opt'n Path". |
21 |
! |
22 |
! "Opt'n Path" is free software: you can redistribute it and/or modify |
23 |
! it under the terms of the GNU Affero General Public License as |
24 |
! published by the Free Software Foundation, either version 3 of the License, |
25 |
! or (at your option) any later version. |
26 |
! |
27 |
! "Opt'n Path" is distributed in the hope that it will be useful, |
28 |
! but WITHOUT ANY WARRANTY; without even the implied warranty of |
29 |
! |
30 |
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the |
31 |
! GNU Affero General Public License for more details. |
32 |
! |
33 |
! You should have received a copy of the GNU Affero General Public License |
34 |
! along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>. |
35 |
! |
36 |
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr, |
37 |
! for commercial licensing opportunities. |
38 |
!---------------------------------------------------------------------- |
39 |
|
40 |
use Io_module |
41 |
use Path_module, only : Nat, NGeomF, XyzGeomF, SGeom,MassAt, & |
42 |
IReparam,NbVar, FormAna, Energies,Order, & |
43 |
Renum, PrintGeomFactor, & |
44 |
Align, NFroz, FrozAtoms, AnaFile,NbVar |
45 |
|
46 |
|
47 |
IMPLICIT NONE |
48 |
|
49 |
! Input |
50 |
! Iteration number |
51 |
INTEGER(KINT), INTENT(IN) :: IOpt |
52 |
! Unit file to print |
53 |
INTEGER(KINT), INTENT(IN) :: FileUnit |
54 |
|
55 |
|
56 |
INTERFACE |
57 |
function valid(string) result (isValid) |
58 |
CHARACTER(*), intent(in) :: string |
59 |
logical :: isValid |
60 |
END function VALID |
61 |
|
62 |
FUNCTION test_zmat(na,ind_zmat) |
63 |
|
64 |
USE Path_module |
65 |
|
66 |
logical :: test_zmat |
67 |
integer(KINT) :: na |
68 |
integer(KINT) :: ind_zmat(Na,5) |
69 |
END FUNCTION TEST_ZMAT |
70 |
|
71 |
|
72 |
SUBROUTINE die(routine, msg, file, line, unit) |
73 |
|
74 |
Use VarTypes |
75 |
Use io_module |
76 |
|
77 |
implicit none |
78 |
|
79 |
character(len=*), intent(in) :: routine, msg |
80 |
character(len=*), intent(in), optional :: file |
81 |
integer(KINT), intent(in), optional :: line, unit |
82 |
|
83 |
END SUBROUTINE die |
84 |
|
85 |
SUBROUTINE Warning(routine, msg, file, line, unit) |
86 |
|
87 |
Use VarTypes |
88 |
Use io_module |
89 |
|
90 |
implicit none |
91 |
|
92 |
character(len=*), intent(in) :: routine, msg |
93 |
character(len=*), intent(in), optional :: file |
94 |
integer(KINT), intent(in), optional :: line, unit |
95 |
|
96 |
END SUBROUTINE Warning |
97 |
|
98 |
END INTERFACE |
99 |
|
100 |
LOGICAL :: Debug, CalcDist |
101 |
INTEGER(KINT) :: I,J,K,Iat |
102 |
REAL(KREAL), ALLOCATABLE :: GeomCart(:,:),GeomCartPrec(:,:) ! Nat,3 |
103 |
REAL(KREAL), ALLOCATABLE :: xRef(:),yRef(:),zRef(:) ! Nat |
104 |
REAL(KREAL), ALLOCATABLE :: Values(:) ! NbVar |
105 |
REAL(KREAL) :: ds |
106 |
REAL(KREAL) :: MRot(3,3), Rmsd |
107 |
CHARACTER(SCHARS) :: Plot="plot" |
108 |
|
109 |
debug=valid("AnaPath") |
110 |
|
111 |
if (debug) Call header("Entering AnaPath") |
112 |
|
113 |
! if (debug) WRITE(*,*) "DBG AnaPaht PrintGeomFactor:",PrintGeomFactor |
114 |
ALLOCATE(GeomCart(Nat,3)) |
115 |
If (NbVar>0) THEN |
116 |
ALLOCATE(Values(NbVar)) |
117 |
END IF |
118 |
|
119 |
CalcDist=.FALSE. |
120 |
|
121 |
WRITE(FileUnit,'("# Iteration ",I5)') Iopt |
122 |
|
123 |
DO J=1,Nat |
124 |
Iat=J |
125 |
IF (renum) Iat=Order(J) |
126 |
GeomCart(J,:)=XyzGeomF(1,:,Iat) |
127 |
END DO |
128 |
|
129 |
|
130 |
! Do we know the curvilinear values ? |
131 |
IF (MOD(IOpt,IReparam)/=0) THEN |
132 |
CalcDist=.TRUE. |
133 |
SGeom=0. |
134 |
ALLOCATE(xRef(Nat),yRef(Nat),zref(Nat),GeomCartPrec(Nat,3)) |
135 |
xRef=GeomCart(:,1) |
136 |
yRef=GeomCart(:,2) |
137 |
zRef=GeomCart(:,3) |
138 |
GeomCartPrec=GeomCart |
139 |
END IF |
140 |
|
141 |
if (debug) THEN |
142 |
WRITE(*,*) "AnaPath - GeomCart - I=",1 |
143 |
DO K=1,Nat |
144 |
WRITE(*,'(1X,I5,3(1X,F15.8))') K,GeomCart(K,1:3) |
145 |
END DO |
146 |
WRITE(*,*) "AnaPath - XYzGeomF(I,:,:) - I=",1 |
147 |
DO K=1,Nat |
148 |
WRITE(*,'(1X,I5,3(1X,F15.8))') K,XyzGeomF(1,:,K) |
149 |
END DO |
150 |
END IF |
151 |
|
152 |
If (NbVar>0) THEN |
153 |
Call AnalyzeGeom(GeomCart,Values) |
154 |
WRITE(FileUnit,FormAna) SGeom(1),Values*PrintGeomFactor,0.d0,Energies(1) |
155 |
if (debug) WRITE(*,FormAna) SGeom(1),Values*PrintGeomFactor,0.d0,Energies(1) |
156 |
ELSE |
157 |
WRITE(FileUnit,FormAna) SGeom(1),0.d0,Energies(1) |
158 |
if (debug) WRITE(*,FormAna) SGeom(1),0.d0,Energies(1) |
159 |
END IF |
160 |
|
161 |
DO I=2,NGeomF |
162 |
DO J=1,Nat |
163 |
Iat=J |
164 |
IF (renum) Iat=Order(J) |
165 |
GeomCart(J,:)=XyzGeomF(I,:,Iat) |
166 |
END DO |
167 |
|
168 |
If (CalcDist) THEN |
169 |
! PFL 2013 Feb 26 |
170 |
! For now, I do _NOT_ align the geometries |
171 |
if (debug) THEN |
172 |
WRITE(*,*) "AnaPath - GeomCart avant align - I=",I |
173 |
DO K=1,Nat |
174 |
WRITE(*,'(1X,I5,3(1X,F15.8))') K,GeomCart(K,1:3) |
175 |
END DO |
176 |
END IF |
177 |
|
178 |
IF ((Nat.GE.4).OR.Align) THEN |
179 |
if (debug) WRITE(*,*) "DBG AnaPath: Aglin 2 geoms" |
180 |
|
181 |
! If we have frozen atoms we align only those ones. |
182 |
if (NFroz.GT.0) THEN |
183 |
Call AlignPartial(Nat,xRef,yRef,zRef, & |
184 |
GeomCart(1,1),GeomCart(1,2),GeomCart(1,3), & |
185 |
FrozAtoms,MRot) |
186 |
ELSE |
187 |
Call CalcRmsd(Nat, xRef,yRef,zRef, & |
188 |
GeomCart(1,1),GeomCart(1,2),GeomCart(1,3), & |
189 |
MRot,rmsd,.TRUE.,.TRUE.) |
190 |
END IF |
191 |
! <- PFL 24 Nov 2008 |
192 |
|
193 |
END IF |
194 |
|
195 |
if (debug) WRITE(*,*) "Mass:",MassAt(1:Nat) |
196 |
ds=0. |
197 |
DO J=1,Nat |
198 |
Iat=J |
199 |
! IF (renum) Iat=Order(J) |
200 |
if (debug) WRITE(*,*) "Mass(J):",J,MassAt(Iat) |
201 |
|
202 |
do K=1,3 |
203 |
ds=ds+MassAt(Iat)*(GeomCartPrec(J,K)-GeomCart(J,K))**2 |
204 |
END DO |
205 |
if (debug) WRITE(*,*) "DBG DS:",J,ds |
206 |
END DO |
207 |
ds=sqrt(ds) |
208 |
if (debug) THEN |
209 |
WRITE(*,*) "AnaPath - GeomCartPrec - I=",I |
210 |
DO K=1,Nat |
211 |
WRITE(*,'(1X,I5,3(1X,F15.8))') K,GeomCartPrec(K,1:3) |
212 |
END DO |
213 |
WRITE(*,*) "DBG Anapaht, ds=",ds |
214 |
END IF |
215 |
|
216 |
SGeom(I)=SGeom(I-1)+ds |
217 |
GeomCartPrec=GeomCart |
218 |
xRef=GeomCart(:,1) |
219 |
yRef=GeomCart(:,2) |
220 |
zRef=GeomCart(:,3) |
221 |
|
222 |
END IF |
223 |
|
224 |
if (debug) THEN |
225 |
WRITE(*,*) "AnaPath - GeomCart - I=",I |
226 |
DO K=1,Nat |
227 |
WRITE(*,'(1X,I5,3(1X,F15.8))') K,GeomCart(K,1:3) |
228 |
END DO |
229 |
END IF |
230 |
|
231 |
If (NbVar>0) THEN |
232 |
Call AnalyzeGeom(GeomCart,Values) |
233 |
WRITE(FileUnit,FormAna) SGeom(i),Values*PrintGeomFactor,(Energies(i)-Energies(1))*ConvE,Energies(i) |
234 |
IF (Debug) WRITE(*,FormAna) SGeom(i),Values*PrintGeomFactor,(Energies(i)-Energies(1))*ConvE,Energies(i) |
235 |
ELSE |
236 |
WRITE(FileUnit,FormAna) SGeom(i),(Energies(i)-Energies(1))*ConvE,Energies(i) |
237 |
If (debug) WRITE(*,FormAna) SGeom(i),(Energies(i)-Energies(1))*ConvE,Energies(i) |
238 |
END IF |
239 |
END DO |
240 |
|
241 |
WRITE(FileUnit,*) "" |
242 |
WRITE(FileUnit,*) "" |
243 |
|
244 |
DeAllocate(GeomCart) |
245 |
If (NbVar>0) DeAllocate(Values) |
246 |
If (CalcDist) Deallocate(GeomCartPrec,xRef,yRef,zRef) |
247 |
|
248 |
Write(IoGplot,'(A,I5,A)') TRIM(Plot) // ' "' // TRIM(AnaFile) // '" i ',Iopt," u xcol:Ecol w lp " |
249 |
Plot="replot" |
250 |
|
251 |
if (debug) Call header("AnaPath over") |
252 |
|
253 |
END SUBROUTINE AnaPath |
254 |
|