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