root / src / ReadInput_gaussian.f90
Historique | Voir | Annoter | Télécharger (7,29 ko)
1 |
SUBROUTINE ReadInput_gaussian |
---|---|
2 |
|
3 |
! This routine reads an input template for Gaussian |
4 |
|
5 |
!---------------------------------------------------------------------- |
6 |
! Copyright 2003-2014 Ecole Normale Supérieure de Lyon, |
7 |
! Centre National de la Recherche Scientifique, |
8 |
! Université Claude Bernard Lyon 1. All rights reserved. |
9 |
! |
10 |
! This work is registered with the Agency for the Protection of Programs |
11 |
! as IDDN.FR.001.100009.000.S.P.2014.000.30625 |
12 |
! |
13 |
! Authors: P. Fleurat-Lessard, P. Dayal |
14 |
! Contact: optnpath@gmail.com |
15 |
! |
16 |
! This file is part of "Opt'n Path". |
17 |
! |
18 |
! "Opt'n Path" is free software: you can redistribute it and/or modify |
19 |
! it under the terms of the GNU Affero General Public License as |
20 |
! published by the Free Software Foundation, either version 3 of the License, |
21 |
! or (at your option) any later version. |
22 |
! |
23 |
! "Opt'n Path" is distributed in the hope that it will be useful, |
24 |
! but WITHOUT ANY WARRANTY; without even the implied warranty of |
25 |
! |
26 |
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the |
27 |
! GNU Affero General Public License for more details. |
28 |
! |
29 |
! You should have received a copy of the GNU Affero General Public License |
30 |
! along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>. |
31 |
! |
32 |
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr, |
33 |
! for commercial licensing opportunities. |
34 |
!---------------------------------------------------------------------- |
35 |
|
36 |
use VarTypes |
37 |
use Path_module |
38 |
use Io_module |
39 |
|
40 |
IMPLICIT NONE |
41 |
|
42 |
INTERFACE |
43 |
function valid(string) result (isValid) |
44 |
CHARACTER(*), intent(in) :: string |
45 |
logical :: isValid |
46 |
END function VALID |
47 |
|
48 |
|
49 |
SUBROUTINE die(routine, msg, file, line, unit) |
50 |
|
51 |
Use VarTypes |
52 |
Use io_module |
53 |
|
54 |
implicit none |
55 |
character(len=*), intent(in) :: routine, msg |
56 |
character(len=*), intent(in), optional :: file |
57 |
integer(KINT), intent(in), optional :: line, unit |
58 |
|
59 |
END SUBROUTINE die |
60 |
|
61 |
|
62 |
END INTERFACE |
63 |
|
64 |
|
65 |
CHARACTER(132) :: Line,LineUp |
66 |
INTEGER(KINT) :: LineL, Idx, Iat |
67 |
INTEGER(KINT) :: I,NTmp |
68 |
REAL(KREAL) :: Lat(3,3) |
69 |
|
70 |
LOGICAL :: Debug |
71 |
|
72 |
|
73 |
Debug=Valid("readinput").OR.Valid("readinput_gaussian") |
74 |
|
75 |
if (debug) Call Header("Entering ReadInput_Gaussian") |
76 |
|
77 |
! We read the Gaussian input file |
78 |
! First, the root |
79 |
IF (DEBUG) WRITE(*,*) "Reading Gauss Root" |
80 |
ALLOCATE(Gauss_Root) |
81 |
NULLIFY(Gauss_Root%next) |
82 |
Current => Gauss_root |
83 |
LineL=1 |
84 |
DO WHILE (LineL.NE.0) |
85 |
READ(IOIN,'(A)') Line |
86 |
Line=AdjustL(Line) |
87 |
LineL=len_Trim(Line) |
88 |
! we do not read the %chk line |
89 |
Idx=INDEX(Line,"chk") |
90 |
IF ((LineL.NE.0).AND.(Idx.EQ.0)) THEN |
91 |
current%Line=TRIM(Line) |
92 |
ALLOCATE(current%next) |
93 |
Current => Current%next |
94 |
Nullify(Current%next) |
95 |
END IF |
96 |
END DO |
97 |
|
98 |
! Current => Gauss_root |
99 |
! DO WHILE (ASSOCIATED(Current%next)) |
100 |
! WRITE(*,'(1X,A)') Trim(current%line) |
101 |
! Current => current%next |
102 |
! END DO |
103 |
|
104 |
! Now the comment... |
105 |
IF (DEBUG) WRITE(*,*) "Reading Gauss Comment" |
106 |
ALLOCATE(Gauss_Comment) |
107 |
NuLLIFY(Gauss_Comment%Next) |
108 |
Current => Gauss_comment |
109 |
LineL=1 |
110 |
DO WHILE (LineL.NE.0) |
111 |
READ(IOIN,'(A)') Line |
112 |
Line=AdjustL(Line) |
113 |
LineL=len(Trim(Line)) |
114 |
IF (LineL.NE.0) THEN |
115 |
current%Line=TRIM(Line) |
116 |
ALLOCATE(current%next) |
117 |
Current => Current%next |
118 |
Nullify(Current%next) |
119 |
END IF |
120 |
END DO |
121 |
|
122 |
! Current => Gauss_comment |
123 |
! DO WHILE (ASSOCIATED(Current%next)) |
124 |
! WRITE(*,'(1X,A)') Trim(current%line) |
125 |
! Current => current%next |
126 |
! END DO |
127 |
|
128 |
! Now the charge |
129 |
IF (DEBUG) WRITE(*,*) "Reading Gauss Charge" |
130 |
READ(IOIN,'(A)') Gauss_Charge |
131 |
if (debug) WRITE(*,*) "Gauss_charge=",TRIM(Gauss_charge) |
132 |
! We now read the Paste part... |
133 |
ALLOCATE(Gauss_Paste(NAt)) |
134 |
LineL=1 |
135 |
Iat=0 |
136 |
IPer=0 |
137 |
FPBC=.FALSE. |
138 |
Gauss_paste=" " |
139 |
DO While (LineL.GT.0) |
140 |
READ(IOIN,'(A)') Line |
141 |
Line=AdjustL(Line) |
142 |
LineL=Len_TRIM(Line) |
143 |
IF (LineL.GT.0) THEN |
144 |
LineUp=Line |
145 |
Call UpCase(LineUp) |
146 |
if (LineUp(1:2)=="TV") THEN |
147 |
FPBC=.TRUE. |
148 |
IPer=IPer+1 |
149 |
If (Iper>3) THEN |
150 |
Call Die("ReadInput Gaussian","Iper>3",Unit=IOOUT) |
151 |
END IF |
152 |
NTmp=Index(LineUp," ") |
153 |
LineUp=LineUp(NTmp:) |
154 |
Read(LineUp,*) Lat(IPer,1:3) |
155 |
ELSE |
156 |
Iat=Iat+1 |
157 |
! we search for additional information at the end of the line |
158 |
! for example ONIOM layers |
159 |
! TO detect the end of the line, we use the fact that all reals |
160 |
! should contain a '.', and that we have 3 reals/line. |
161 |
Idx=Index(Line,'.') |
162 |
Line=ADJUSTL(Line(Idx+1:)) |
163 |
Idx=Index(Line,'.') |
164 |
Line=ADJUSTL(Line(Idx+1:)) |
165 |
Idx=Index(Line,'.') |
166 |
Line=ADJUSTL(Line(Idx+1:)) |
167 |
Idx=Index(Line,' ') |
168 |
If (Idx>0) THEN |
169 |
Line=ADJUSTL(Line(Idx:)) |
170 |
IF (LEN_TRIM(Line).GT.0) THEN |
171 |
Gauss_paste(Iat)=ADJUSTL(TRIM(Line)) |
172 |
END IF |
173 |
ELSE |
174 |
Gauss_paste(Iat)="" |
175 |
END IF |
176 |
END IF |
177 |
END IF |
178 |
|
179 |
END DO |
180 |
|
181 |
|
182 |
IF (Iat.NE.Nat) THEN |
183 |
WRITE(Line,*) "I found ", Iat," lines for the geometry instead of ",Nat |
184 |
Call Die("ReadInput Gaussian","Line",UNIT=IOOUT) |
185 |
END IF |
186 |
|
187 |
IF (FPBC) THEN |
188 |
Lat_a(1:3)=Lat(1,1:3) |
189 |
Lat_b(1:3)=Lat(2,1:3) |
190 |
Lat_c(1:3)=Lat(3,1:3) |
191 |
If (IPer>=1) THEN |
192 |
kaBeg=-1 |
193 |
kaEnd=1 |
194 |
END IF |
195 |
If (IPer>=2) THEN |
196 |
kbBeg=-1 |
197 |
kbEnd=1 |
198 |
END IF |
199 |
If (IPer==3) THEN |
200 |
kcBeg=-1 |
201 |
kcEnd=1 |
202 |
END IF |
203 |
If (IPer>3) THEN |
204 |
Call Die("Readinput_gaussian","Found too many Tv lines !",Unit=IOOUT) |
205 |
END IF |
206 |
END IF |
207 |
|
208 |
|
209 |
! We now read the last part |
210 |
IF (DEBUG) WRITE(*,*) "Reading Gauss End" |
211 |
! READ(IOIN,'(A)') Line |
212 |
ALLOCATE(Gauss_End) |
213 |
NuLLIFY(Gauss_End%Next) |
214 |
Current => Gauss_End |
215 |
LineL=1 |
216 |
DO WHILE (1.EQ.1) |
217 |
READ(IOIN,'(A)',END=999) Line |
218 |
Line=AdjustL(Line) |
219 |
LineL=len(Trim(Line)) |
220 |
current%Line=TRIM(Line) |
221 |
ALLOCATE(current%next) |
222 |
Current => Current%next |
223 |
Nullify(Current%next) |
224 |
END DO |
225 |
999 CONTINUE |
226 |
|
227 |
IF (Debug) THEN |
228 |
! Write the gaussian input file for testing purposes |
229 |
Current => Gauss_root |
230 |
DO WHILE (ASSOCIATED(Current%next)) |
231 |
WRITE(*,'(1X,A)') Trim(current%line) |
232 |
Current => current%next |
233 |
END DO |
234 |
|
235 |
WRITE(*,*) |
236 |
! WRITE(*,*) '//INFO// Comment original:' |
237 |
|
238 |
Current => Gauss_comment |
239 |
DO WHILE (ASSOCIATED(Current%next)) |
240 |
WRITE(*,'(1X,A)') Trim(current%line) |
241 |
Current => current%next |
242 |
END DO |
243 |
|
244 |
WRITE(*,*) |
245 |
WRITE(*,*) Trim(Gauss_charge) |
246 |
|
247 |
DO I=1,Nat |
248 |
WRITE(*,'(1X,A10,3(1X,F15.8),1X,A)') Trim(AtName(I)),XyzGeomI(1,1:3,I), TRIM(Gauss_Paste(I)) |
249 |
END DO |
250 |
|
251 |
WRITE(*,*) |
252 |
Current => Gauss_End |
253 |
DO WHILE (ASSOCIATED(Current%next)) |
254 |
WRITE(*,'(1X,A)') Trim(current%line) |
255 |
Current => current%next |
256 |
END DO |
257 |
|
258 |
WRITE(*,*) |
259 |
|
260 |
Call Header("Exiting ReadInput_Gaussian") |
261 |
|
262 |
END IF |
263 |
|
264 |
|
265 |
|
266 |
END SUBROUTINE READINPUT_GAUSSIAN |