root / src / Write_path.f90
Historique | Voir | Annoter | Télécharger (6,19 ko)
1 | 1 | pfleura2 | SUBROUTINE Write_path(Iopt) |
---|---|---|---|
2 | 12 | pfleura2 | !---------------------------------------------------------------------- |
3 | 12 | pfleura2 | ! Copyright 2003-2014 Ecole Normale Supérieure de Lyon, |
4 | 12 | pfleura2 | ! Centre National de la Recherche Scientifique, |
5 | 12 | pfleura2 | ! Université Claude Bernard Lyon 1. All rights reserved. |
6 | 12 | pfleura2 | ! |
7 | 12 | pfleura2 | ! This work is registered with the Agency for the Protection of Programs |
8 | 12 | pfleura2 | ! as IDDN.FR.001.100009.000.S.P.2014.000.30625 |
9 | 12 | pfleura2 | ! |
10 | 12 | pfleura2 | ! Authors: P. Fleurat-Lessard, P. Dayal |
11 | 12 | pfleura2 | ! Contact: optnpath@gmail.com |
12 | 12 | pfleura2 | ! |
13 | 12 | pfleura2 | ! This file is part of "Opt'n Path". |
14 | 12 | pfleura2 | ! |
15 | 12 | pfleura2 | ! "Opt'n Path" is free software: you can redistribute it and/or modify |
16 | 12 | pfleura2 | ! it under the terms of the GNU Affero General Public License as |
17 | 12 | pfleura2 | ! published by the Free Software Foundation, either version 3 of the License, |
18 | 12 | pfleura2 | ! or (at your option) any later version. |
19 | 12 | pfleura2 | ! |
20 | 12 | pfleura2 | ! "Opt'n Path" is distributed in the hope that it will be useful, |
21 | 12 | pfleura2 | ! but WITHOUT ANY WARRANTY; without even the implied warranty of |
22 | 12 | pfleura2 | ! |
23 | 12 | pfleura2 | ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the |
24 | 12 | pfleura2 | ! GNU Affero General Public License for more details. |
25 | 12 | pfleura2 | ! |
26 | 12 | pfleura2 | ! You should have received a copy of the GNU Affero General Public License |
27 | 12 | pfleura2 | ! along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>. |
28 | 12 | pfleura2 | ! |
29 | 12 | pfleura2 | ! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr, |
30 | 12 | pfleura2 | ! for commercial licensing opportunities. |
31 | 12 | pfleura2 | !---------------------------------------------------------------------- |
32 | 1 | pfleura2 | |
33 | 1 | pfleura2 | Use Path_module |
34 | 1 | pfleura2 | Use Io_module |
35 | 1 | pfleura2 | |
36 | 1 | pfleura2 | IMPLICIT NONE |
37 | 1 | pfleura2 | |
38 | 1 | pfleura2 | INTEGER(KINT), INTENT(IN) :: Iopt |
39 | 1 | pfleura2 | |
40 | 2 | pfleura2 | INTEGER(KINT) :: IGeom, Iat, I |
41 | 1 | pfleura2 | REAL(KREAL), ALLOCATABLE :: GeomTmpC(:), GeomTmp(:),GeomTmpC2(:,:) |
42 | 1 | pfleura2 | CHARACTER(SCHARS) :: Line |
43 | 1 | pfleura2 | CHARACTER(LCHARS) ::Title |
44 | 1 | pfleura2 | LOGICAL :: Debug |
45 | 1 | pfleura2 | |
46 | 1 | pfleura2 | INTERFACE |
47 | 1 | pfleura2 | function valid(string) result (isValid) |
48 | 1 | pfleura2 | CHARACTER(*), intent(in) :: string |
49 | 1 | pfleura2 | logical :: isValid |
50 | 1 | pfleura2 | END function VALID |
51 | 1 | pfleura2 | END INTERFACE |
52 | 1 | pfleura2 | |
53 | 1 | pfleura2 | debug=valid('write_path').OR.valid('writepath') |
54 | 1 | pfleura2 | if (debug) Call Header("Entering Write_PATH") |
55 | 1 | pfleura2 | |
56 | 1 | pfleura2 | |
57 | 1 | pfleura2 | ALLOCATE(GeomTmpC(3*Nat), GeomTmp(NCoord),GeomTmpC2(Nat,3)) |
58 | 1 | pfleura2 | |
59 | 1 | pfleura2 | IF (IOpt.GE.0) THEN |
60 | 1 | pfleura2 | WRITE(Line,'(I5)') Iopt |
61 | 1 | pfleura2 | ELSE |
62 | 1 | pfleura2 | Line="Ini" |
63 | 1 | pfleura2 | Energies=0. |
64 | 1 | pfleura2 | END IF |
65 | 1 | pfleura2 | OPEN(IOTMP,File=Trim(PathName) // '.' // AdjustL(TRIM(Line))) |
66 | 1 | pfleura2 | IF ((COORD.EQ.'ZMAT').OR.(COORD.EQ.'MIXED').OR.(COORD.EQ.'BAKER')) & |
67 | 1 | pfleura2 | OPEN(IOCART,File=TRIM(PathName) // '_cart.' // AdjustL(TRIM(Line))) |
68 | 1 | pfleura2 | |
69 | 1 | pfleura2 | DO IGeom=1,NGeomF |
70 | 1 | pfleura2 | WRITE(Title,"('Geometry ',I3,'/',I3,' for iteration ',I3,' E=',F13.6)") Igeom,NgeomF,Iopt,Energies(IGeom) |
71 | 1 | pfleura2 | SELECT CASE(Coord) |
72 | 1 | pfleura2 | CASE ('CART','HYBRID') |
73 | 1 | pfleura2 | ! XyzGeomF is 3,Nat... but Printgeom expects Nat,3... |
74 | 1 | pfleura2 | ! this should really be rewritten !!!! |
75 | 1 | pfleura2 | GeomTmp=Reshape(reshape(XyzGeomF(IGeom,:,:),(/Nat,3/),ORDER=(/2,1/)),(/3*Nat/)) |
76 | 1 | pfleura2 | CASE ('ZMAT','MIXED','BAKER') |
77 | 1 | pfleura2 | GeomTmp=IntCoordF(IGeom,:) |
78 | 1 | pfleura2 | CASE DEFAULT |
79 | 1 | pfleura2 | WRITE(*,*) "Coord=",TRIM(Coord)," not recognized in Write_path. L34.STOP" |
80 | 1 | pfleura2 | STOP |
81 | 1 | pfleura2 | END SELECT |
82 | 1 | pfleura2 | |
83 | 1 | pfleura2 | ! Nothing for the baker case. |
84 | 1 | pfleura2 | Call PrintGeom(Title,Nat,NCoord,GeomTmp,Coord,IoTmp,Atome,Order,OrderInv,IndZmat) |
85 | 1 | pfleura2 | |
86 | 1 | pfleura2 | IF (COORD.EQ.'ZMAT') THEN |
87 | 1 | pfleura2 | ! Writing the Cartesian coordinates |
88 | 1 | pfleura2 | WRITE(IOCART,'(1X,I5)') Nat |
89 | 1 | pfleura2 | WRITE(IOCART,'(1X,A)') Title |
90 | 1 | pfleura2 | ! we have to generate the cartesian coordinates from the internal coordinates |
91 | 1 | pfleura2 | Call Int2Cart(nat,indzmat,GeomTmp,GeomTmpC) |
92 | 1 | pfleura2 | GeomTmpC2=reshape(GeomTmpC,(/Nat,3/)) |
93 | 1 | pfleura2 | DO I=1,Nat |
94 | 1 | pfleura2 | IF (renum) THEN |
95 | 1 | pfleura2 | Iat=Order(I) |
96 | 1 | pfleura2 | ! WRITE(IOCART,'(1X,A10,3(1X,F15.8))') Trim(AtName(I)),GeomTmpC(3*Iat-2:3*Iat) |
97 | 1 | pfleura2 | WRITE(IOCART,'(1X,A10,3(1X,F15.8))') Trim(AtName(I)),GeomTmpC2(Iat,1:3) |
98 | 1 | pfleura2 | ELSE |
99 | 1 | pfleura2 | Iat=OrderInv(I) |
100 | 1 | pfleura2 | ! WRITE(IOCART,'(1X,A10,3(1X,F15.8),A)') Trim(AtName(Iat)),GeomTmpC(3*I-2:3*I) |
101 | 1 | pfleura2 | WRITE(IOCART,'(1X,A10,3(1X,F15.8),A)') Trim(AtName(Iat)),GeomTmpC2(I,1:3) |
102 | 1 | pfleura2 | END IF |
103 | 1 | pfleura2 | END DO |
104 | 1 | pfleura2 | END IF ! matches IF (COORD.EQ.'ZMAT') THEN |
105 | 1 | pfleura2 | |
106 | 1 | pfleura2 | IF (COORD.EQ.'BAKER') THEN |
107 | 1 | pfleura2 | ! Writing the Cartesian coordinates |
108 | 1 | pfleura2 | WRITE(IOCART,'(1X,I5)') Nat |
109 | 1 | pfleura2 | WRITE(IOCART,'(1X,A)') Title |
110 | 1 | pfleura2 | ! we have to generate the cartesian coordinates from the internal coordinates |
111 | 1 | pfleura2 | ! we can also print the cartesiann coordinates directly from XyzGeomF?? |
112 | 1 | pfleura2 | !Call ConvertBakerInternal_cart(InCoordF(IGeom-1,:),InCoordF(IGeom,:)) |
113 | 1 | pfleura2 | ! XyzGeomF(NGeomF,3,Nat), GeomTmpC(3*Nat),GeomTmpC2(Nat,3) |
114 | 1 | pfleura2 | !GeomTmpC2=reshape(GeomTmpC,(/Nat,3/)). XyzGeomF is already updated in |
115 | 1 | pfleura2 | ! EgradPath.f90 |
116 | 1 | pfleura2 | DO I =1, 3 |
117 | 1 | pfleura2 | GeomTmpC2(:,I)=XyzGeomF(IGeom,I,:) |
118 | 1 | pfleura2 | END DO |
119 | 1 | pfleura2 | DO I=1,Nat |
120 | 1 | pfleura2 | IF (renum) THEN |
121 | 1 | pfleura2 | Iat=Order(I) |
122 | 1 | pfleura2 | ! WRITE(IOCART,'(1X,A10,3(1X,F15.8))') Trim(AtName(I)),GeomTmpC(3*Iat-2:3*Iat) |
123 | 1 | pfleura2 | !Print *, GeomTmpC2(Iat,1:3) |
124 | 1 | pfleura2 | WRITE(IOCART,'(1X,A10,3(1X,F15.8))') Trim(AtName(I)),GeomTmpC2(Iat,1:3) |
125 | 1 | pfleura2 | ELSE |
126 | 1 | pfleura2 | Iat=OrderInv(I) |
127 | 1 | pfleura2 | ! WRITE(IOCART,'(1X,A10,3(1X,F15.8),A)') Trim(AtName(Iat)),GeomTmpC(3*I-2:3*I) |
128 | 1 | pfleura2 | WRITE(IOCART,'(1X,A10,3(1X,F15.8),A)') Trim(AtName(Iat)),GeomTmpC2(I,1:3) |
129 | 1 | pfleura2 | END IF |
130 | 1 | pfleura2 | END DO |
131 | 1 | pfleura2 | END IF ! matches IF (COORD.EQ.'BAKER') THEN |
132 | 1 | pfleura2 | |
133 | 1 | pfleura2 | IF (COORD.EQ.'MIXED') THEN |
134 | 1 | pfleura2 | ! Writing the Cartesian coordinates |
135 | 1 | pfleura2 | WRITE(IOCART,'(1X,I5)') Nat |
136 | 1 | pfleura2 | WRITE(IOCART,'(1X,A)') Title |
137 | 1 | pfleura2 | ! we have to generate the cartesian coordinates from the internal coordinates |
138 | 1 | pfleura2 | Call Mixed2Cart(nat,indzmat,geomtmp,GeomTmpC) |
139 | 1 | pfleura2 | GeomTmpC2=reshape(GeomTmpC,(/Nat,3/)) |
140 | 1 | pfleura2 | DO I=1,Nat |
141 | 1 | pfleura2 | IF (renum) THEN |
142 | 1 | pfleura2 | Iat=Order(I) |
143 | 1 | pfleura2 | ! WRITE(IOCART,'(1X,A10,3(1X,F15.8))') Trim(AtName(I)),GeomTmpC(3*Iat-2:3*Iat) |
144 | 1 | pfleura2 | WRITE(IOCART,'(1X,A10,3(1X,F15.8))') Trim(AtName(I)),GeomTmpC2(Iat,1:3) |
145 | 1 | pfleura2 | ELSE |
146 | 1 | pfleura2 | Iat=OrderInv(I) |
147 | 1 | pfleura2 | ! WRITE(IOCART,'(1X,A10,3(1X,F15.8),A)') Trim(AtName(Iat)),GeomTmpC(3*I-2:3*I) |
148 | 1 | pfleura2 | WRITE(IOCART,'(1X,A10,3(1X,F15.8),A)') Trim(AtName(Iat)),GeomTmpC2(I,1:3) |
149 | 1 | pfleura2 | END IF |
150 | 1 | pfleura2 | END DO |
151 | 1 | pfleura2 | END IF ! matches IF (COORD.EQ.'MIXED') THEN |
152 | 1 | pfleura2 | END DO ! matches DO IGeom=1,NGeomF |
153 | 1 | pfleura2 | CLOSE(IOTMP) |
154 | 1 | pfleura2 | IF ((COORD.EQ.'ZMAT').OR.(COORD.EQ.'MIXED').OR.(COORD.EQ.'BAKER')) CLOSE(IOCART) |
155 | 1 | pfleura2 | DEALLOCATE(GeomTmpC,GeomTmp) |
156 | 1 | pfleura2 | |
157 | 1 | pfleura2 | if (debug) Call Header('Exiting Write_PATH') |
158 | 1 | pfleura2 | END SUBROUTINE Write_path |