root / src / Calc_Xprim.f90
Historique | Voir | Annoter | Télécharger (8,04 ko)
1 |
SUBROUTINE Calc_Xprim(nat,x,y,z,Coordinate,NPrim,XPrimitive,XPrimRef) |
---|---|
2 |
! |
3 |
! This subroutine uses the description of a list of Coordinates |
4 |
! to compute the values of the coordinates for a given geometry. |
5 |
! |
6 |
!!!!!!!!!! |
7 |
! Input: |
8 |
! Na: INTEGER, Number of atoms |
9 |
! x,y,z(Na): REAL, cartesian coordinates of the considered geometry |
10 |
! Coordinate (Pointer(ListCoord)): description of the wanted coordiantes |
11 |
! NPrim, INTEGER: Number of coordinates to compute |
12 |
! |
13 |
! Optional: XPrimRef(NPrim) REAL: array that contains coordinates values for |
14 |
! a former geometry. Useful for Dihedral angles evolution... |
15 |
|
16 |
!!!!!!!!!!! |
17 |
! Output: |
18 |
! XPrimimite(NPrim) REAL: array that will contain the values of the coordinates |
19 |
! |
20 |
!!!!!!!!! |
21 |
|
22 |
!---------------------------------------------------------------------- |
23 |
! Copyright 2003-2014 Ecole Normale Supérieure de Lyon, |
24 |
! Centre National de la Recherche Scientifique, |
25 |
! Université Claude Bernard Lyon 1. All rights reserved. |
26 |
! |
27 |
! This work is registered with the Agency for the Protection of Programs |
28 |
! as IDDN.FR.001.100009.000.S.P.2014.000.30625 |
29 |
! |
30 |
! Authors: P. Fleurat-Lessard, P. Dayal |
31 |
! Contact: optnpath@gmail.com |
32 |
! |
33 |
! This file is part of "Opt'n Path". |
34 |
! |
35 |
! "Opt'n Path" is free software: you can redistribute it and/or modify |
36 |
! it under the terms of the GNU Affero General Public License as |
37 |
! published by the Free Software Foundation, either version 3 of the License, |
38 |
! or (at your option) any later version. |
39 |
! |
40 |
! "Opt'n Path" is distributed in the hope that it will be useful, |
41 |
! but WITHOUT ANY WARRANTY; without even the implied warranty of |
42 |
! |
43 |
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the |
44 |
! GNU Affero General Public License for more details. |
45 |
! |
46 |
! You should have received a copy of the GNU Affero General Public License |
47 |
! along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>. |
48 |
! |
49 |
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr, |
50 |
! for commercial licensing opportunities. |
51 |
!---------------------------------------------------------------------- |
52 |
|
53 |
Use VarTypes |
54 |
Use Io_module |
55 |
Use Path_module, only : pi |
56 |
|
57 |
IMPLICIT NONE |
58 |
|
59 |
Type (ListCoord), POINTER :: Coordinate |
60 |
INTEGER(KINT), INTENT(IN) :: Nat,NPrim |
61 |
REAL(KREAL), INTENT(IN) :: x(Nat), y(Nat), z(Nat) |
62 |
REAL(KREAL), INTENT(IN), OPTIONAL :: XPrimRef(NPrim) |
63 |
REAL(KREAL), INTENT(OUT) :: XPrimitive(NPrim) |
64 |
|
65 |
|
66 |
Type (ListCoord), POINTER :: ScanCoord |
67 |
|
68 |
real(KREAL) :: vx1,vy1,vz1,norm1 |
69 |
real(KREAL) :: vx2,vy2,vz2,norm2 |
70 |
real(KREAL) :: vx3,vy3,vz3,norm3 |
71 |
real(KREAL) :: vx4,vy4,vz4,norm4 |
72 |
real(KREAL) :: vx5,vy5,vz5,norm5 |
73 |
|
74 |
INTEGER(KINT) :: I |
75 |
|
76 |
REAL(KREAL) :: DiheTmp |
77 |
|
78 |
LOGICAL :: debug, debugPFL |
79 |
|
80 |
INTERFACE |
81 |
function valid(string) result (isValid) |
82 |
CHARACTER(*), intent(in) :: string |
83 |
logical :: isValid |
84 |
END function VALID |
85 |
|
86 |
FUNCTION angle(v1x,v1y,v1z,norm1,v2x,v2y,v2z,norm2) |
87 |
use Path_module, only : Pi,KINT, KREAL |
88 |
real(KREAL) :: v1x,v1y,v1z,norm1 |
89 |
real(KREAL) :: v2x,v2y,v2z,norm2 |
90 |
real(KREAL) :: angle |
91 |
END FUNCTION ANGLE |
92 |
|
93 |
FUNCTION SinAngle(v1x,v1y,v1z,norm1,v2x,v2y,v2z,norm2) |
94 |
use Path_module, only : Pi,KINT, KREAL |
95 |
real(KREAL) :: v1x,v1y,v1z,norm1 |
96 |
real(KREAL) :: v2x,v2y,v2z,norm2 |
97 |
real(KREAL) :: SinAngle |
98 |
END FUNCTION SINANGLE |
99 |
|
100 |
|
101 |
FUNCTION angle_d(v1x,v1y,v1z,norm1,v2x,v2y,v2z,norm2,v3x,v3y,v3z,norm3) |
102 |
use Path_module, only : Pi,KINT, KREAL |
103 |
real(KREAL) :: v1x,v1y,v1z,norm1 |
104 |
real(KREAL) :: v2x,v2y,v2z,norm2 |
105 |
real(KREAL) :: v3x,v3y,v3z,norm3 |
106 |
real(KREAL) :: angle_d,ca,sa |
107 |
END FUNCTION ANGLE_D |
108 |
|
109 |
END INTERFACE |
110 |
|
111 |
|
112 |
debug=valid("Calc_Xprim") |
113 |
debugPFL=valid("BakerPFL") |
114 |
|
115 |
if (debug) Call Header("Entering Cal_XPrim") |
116 |
|
117 |
|
118 |
IF (debug) THEN |
119 |
WRITE(*,*) "DBG Calc_Xprim, geom" |
120 |
DO I=1,Nat |
121 |
WRITE(*,'(1X,I5,3(1X,F15.3))') I,X(I),y(i),z(i) |
122 |
END DO |
123 |
IF (Present(XPrimRef)) THEN |
124 |
WRITE(*,*) "XPrimRef" |
125 |
WRITE(*,'(15(1X,F10.6))') XPrimRef |
126 |
END IF |
127 |
WRITE(*,*) "NPrim:",NPrim |
128 |
END IF |
129 |
|
130 |
|
131 |
! WRITE(*,*) "Coordinate:",associated(Coordinate),coordinate%Type |
132 |
|
133 |
ScanCoord => Coordinate |
134 |
|
135 |
! WRITE(*,*) "ScanCoord:",associated(ScanCoord),ScanCoord%Type |
136 |
|
137 |
! WRITE(*,*) "coucou" |
138 |
I=0 ! index for the NPrim (NPrim is the number of primitive coordinates). |
139 |
DO WHILE (Associated(ScanCoord%next)) |
140 |
I=I+1 |
141 |
! WRITE(*,*) i |
142 |
SELECT CASE (ScanCoord%Type) |
143 |
CASE ('BOND') |
144 |
Call vecteur(ScanCoord%At2,ScanCoord%At1,x,y,z,vx2,vy2,vz2,Norm2) |
145 |
Xprimitive(I) = Norm2 |
146 |
CASE ('ANGLE') |
147 |
Call vecteur(ScanCoord%At2,ScanCoord%At3,x,y,z,vx1,vy1,vz1,Norm1) |
148 |
Call vecteur(ScanCoord%At2,ScanCoord%At1,x,y,z,vx2,vy2,vz2,Norm2) |
149 |
Xprimitive(I) = angle(vx1,vy1,vz1,Norm1,vx2,vy2,vz2,Norm2)*Pi/180. |
150 |
CASE ('DIHEDRAL') |
151 |
Call vecteur(ScanCoord%At2,ScanCoord%At1,x,y,z,vx1,vy1,vz1,Norm1) |
152 |
Call vecteur(ScanCoord%At2,ScanCoord%At3,x,y,z,vx2,vy2,vz2,Norm2) |
153 |
Call vecteur(ScanCoord%At3,ScanCoord%At4,x,y,z,vx3,vy3,vz3,Norm3) |
154 |
Call produit_vect(vx1,vy1,vz1,vx2,vy2,vz2, & |
155 |
vx4,vy4,vz4,norm4) |
156 |
Call produit_vect(vx3,vy3,vz3,vx2,vy2,vz2, & |
157 |
vx5,vy5,vz5,norm5) |
158 |
|
159 |
DiheTmp= angle_d(vx4,vy4,vz4,norm4,vx5,vy5,vz5,norm5, & |
160 |
vx2,vy2,vz2,norm2) |
161 |
Xprimitive(I) = DiheTmp*Pi/180. |
162 |
! PFL 15th March 2008 -> |
163 |
! I think that the test on changes less than Pi should be enough |
164 |
!! We treat large dihedral angles differently as +180=-180 mathematically and physically |
165 |
!! but this causes lots of troubles when converting baker to cart. |
166 |
!! So we ensure that large dihedral angles always have the same sign |
167 |
! if (abs(ScanCoord%SignDihedral).NE.1) THEN |
168 |
! ScanCoord%SignDihedral=Int(Sign(1.D0,DiheTmp)) |
169 |
! ELSE |
170 |
! If ((abs(DiheTmp).GE.170.D0).AND.(Sign(1.,DiheTmp)*ScanCoord%SignDihedral<0)) THEN |
171 |
! Xprimitive(I) = DiheTmp*Pi/180.+ ScanCoord%SignDihedral*2.*Pi |
172 |
! END IF |
173 |
! END IF |
174 |
!!!! <- PFL 15th March 2008 |
175 |
! Another test... will all this be consistent ??? |
176 |
! We want the shortest path, so we check that the change in dihedral angles is less than Pi: |
177 |
IF (Present(XPrimRef)) THEN |
178 |
IF (abs(Xprimitive(I)-XPrimRef(I)).GE.Pi) THEN |
179 |
if (debug) THEN |
180 |
WRITE(*,*) "Pb dihedral, i,Xprimivite,XPrimref=",i,XPrimitive(I),XPrimRef(I) |
181 |
WRITE(*,*) "In deg Xprimivite,XPrimref=",XPrimitive(I)*180./Pi,XPrimRef(I)*180/Pi |
182 |
END IF |
183 |
if ((Xprimitive(I)-XPrimRef(I)).GE.Pi) THEN |
184 |
Xprimitive(I)=Xprimitive(I)-2.d0*Pi |
185 |
ELSE |
186 |
Xprimitive(I)=Xprimitive(I)+2.d0*Pi |
187 |
END IF |
188 |
END IF |
189 |
if (debug) WRITE(*,*) " New Xprimivite",XPrimitive(I),XPrimitive(I)*180./Pi |
190 |
END IF |
191 |
CASE DEFAULT |
192 |
WRITE(*,*) "Scancoord%type unknown for I",I,scancoord%type |
193 |
END SELECT |
194 |
ScanCoord => ScanCoord%next |
195 |
END DO ! matches DO WHILE (Associated(ScanCoord%next)) |
196 |
|
197 |
|
198 |
|
199 |
IF (debug) THEN |
200 |
WRITE(*,*) "DBG Calc_Xprim Values" |
201 |
WRITE(*,*) "Found ",I," primitives" |
202 |
|
203 |
ScanCoord=>Coordinate |
204 |
I=0 ! index for the NPrim (NPrim is the number of primitive coordinates). |
205 |
DO WHILE (Associated(ScanCoord%next)) |
206 |
I=I+1 |
207 |
SELECT CASE (ScanCoord%Type) |
208 |
CASE ('BOND') |
209 |
WRITE(*,'(1X,I3,":",I5," - ",I5," = ",F15.6)') I,ScanCoord%At1,ScanCoord%At2,Xprimitive(I) |
210 |
CASE ('ANGLE') |
211 |
WRITE(*,'(1X,I3,":",I5," - ",I5," - ",I5," = ",F15.6)') I,ScanCoord%At1, & |
212 |
ScanCoord%At2, ScanCoord%At3,Xprimitive(I)*180./Pi |
213 |
CASE ('DIHEDRAL') |
214 |
WRITE(*,'(1X,I3,":",I5," - ",I5," - ",I5," - ",I5," = ",F15.6)') I,ScanCoord%At1,& |
215 |
ScanCoord%At2, ScanCoord%At3,ScanCoord%At4,Xprimitive(I)*180./Pi |
216 |
END SELECT |
217 |
ScanCoord => ScanCoord%next |
218 |
END DO ! matches DO WHILE (Associated(ScanCoord%next)) |
219 |
END IF |
220 |
|
221 |
if (debug) Call Header(" Cal_XPrim OVER ") |
222 |
|
223 |
END SUBROUTINE Calc_Xprim |