root / src / ReadInput_vasp.f90
Historique | Voir | Annoter | Télécharger (6,13 ko)
1 |
SUBROUTINE ReadInput_Vasp |
---|---|
2 |
|
3 |
! This routine reads an input template for Vasp |
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 |
END INTERFACE |
48 |
|
49 |
CHARACTER(LCHARS) :: Line |
50 |
INTEGER(KINT) :: Iat |
51 |
INTEGER(KINT) :: I,J |
52 |
|
53 |
INTEGER(KINT), ALLOCATABLE :: NbAtType(:) !na |
54 |
INTEGER(KINT) :: NbType, NbTypeUser |
55 |
|
56 |
REAL(KREAL) :: B(3),xtmp,ytmp,ztmp |
57 |
|
58 |
LOGICAL :: TChk |
59 |
|
60 |
LOGICAL :: Debug |
61 |
|
62 |
|
63 |
Debug=Valid("readinput").OR.Valid("readinput_vasp") |
64 |
|
65 |
if (debug) Call Header("Entering ReadInput_Vasp") |
66 |
|
67 |
FPBC=.TRUE. |
68 |
|
69 |
if (Input/="VASP") THEN |
70 |
|
71 |
! Input was not Vasp, so many parameters are missing like lattice |
72 |
! constants... |
73 |
! we read them now ! |
74 |
ALLOCATE(FFF(3,nat)) |
75 |
! First geometry is a bit special for VASP as we have to set |
76 |
! many things |
77 |
IF (DEBUG) WRITE(*,*) "Reading Vasp Parameters" |
78 |
READ(IOIN,'(A)') Vasp_Title |
79 |
READ(IOIN,*) Vasp_param |
80 |
|
81 |
READ(IOIN,*) Lat_a |
82 |
READ(IOIN,*) Lat_b |
83 |
READ(IOIN,*) Lat_c |
84 |
|
85 |
Lat_a=Lat_a*Vasp_param |
86 |
Lat_b=Lat_b*Vasp_param |
87 |
Lat_c=Lat_c*Vasp_param |
88 |
|
89 |
ALLOCATE(NbAtType(nat)) |
90 |
READ(IOIN,'(A)') Vasp_types |
91 |
! First, how many different types ? |
92 |
NbAtType=0 |
93 |
READ(Vasp_types,*,END=998) NbAtType |
94 |
998 CONTINUE |
95 |
NbType=0 |
96 |
DO WHILE (NbAtType(NbType+1).NE.0) |
97 |
NbType=NbType+1 |
98 |
END DO |
99 |
|
100 |
! Do we know the atom types ? |
101 |
IF (AtTypes(1).EQ.' ') THEN |
102 |
! user has not provided atom types... we have to find them ourselves |
103 |
! by looking into the POTCAR file... |
104 |
INQUIRE(File="POTCAR", EXIST=Tchk) |
105 |
IF (.NOT.Tchk) THEN |
106 |
WRITE(*,*) "ERROR! No AtTypes provided, and POTCAR file not found" |
107 |
STOP |
108 |
END IF |
109 |
OPEN(IOTMP,File="POTCAR") |
110 |
DO I=1,NbType |
111 |
Line='Empty' |
112 |
DO WHILE (Line(1:2).NE.'US') |
113 |
READ(IOTMP,'(A)') Line |
114 |
Line=AdjustL(Line) |
115 |
END DO |
116 |
Line=adjustl(Line(3:)) |
117 |
AtTypes(I)=Line(1:2) |
118 |
END DO |
119 |
if (debug) WRITE(*,'(A,100(1X,A2))') "ReadG:VASP AtTypes",AtTypes(1:NbType) |
120 |
CLOSE(IOTMP) |
121 |
|
122 |
ELSE !AtTypes(1).EQ.' ' |
123 |
! user has provided atom types |
124 |
NbTypeUser=0 |
125 |
DO WHILE (AtTypes(NbTypeUser+1).NE.' ') |
126 |
NbTypeUser=NbTypeUser+1 |
127 |
END DO |
128 |
IF (NbType.NE.NbTypeUser) THEN |
129 |
WRITE(*,*) "ERROR Read_Geom : NbType in POSCAR do not match AtTypes" |
130 |
STOP |
131 |
END IF |
132 |
END IF |
133 |
|
134 |
IAt=1 |
135 |
DO I=1,NbType |
136 |
DO J=1,NbAtType(I) |
137 |
AtName(Iat)=AtTypes(I) |
138 |
Iat=Iat+1 |
139 |
END DO |
140 |
END DO |
141 |
DEALLOCATE(NbAtType) |
142 |
|
143 |
NbTypes=NbType |
144 |
|
145 |
READ(IOIN,'(A)') Vasp_comment |
146 |
READ(IOIN,'(A)') Vasp_direct |
147 |
V_direct=Adjustl(Vasp_direct) |
148 |
Call UpCase(V_direct) |
149 |
|
150 |
! PFL 2011 Mar 8 -> |
151 |
! We have to read the FFF flags : |
152 |
DO I=1,Nat |
153 |
READ(IOIN,*) Xtmp,ytmp,ztmp,FFF(1:3,I) |
154 |
DO J=1,3 |
155 |
FFF(J,I)=AdjustL(FFF(J,I)) |
156 |
CALL Upcase(FFF(J,I)) |
157 |
END DO |
158 |
END DO |
159 |
! <- PFL 2011 Mar 8 |
160 |
|
161 |
END IF |
162 |
|
163 |
! In the case of VASP there is always the problem of moving from one side |
164 |
! of the box to the other... |
165 |
|
166 |
Renum=.TRUE. |
167 |
|
168 |
! V_direct has been set in Read_geom |
169 |
IF (V_direct(1:6).EQ.'DIRECT') THEN |
170 |
Latr(1:3,1)=Lat_a |
171 |
Latr(1:3,2)=Lat_b |
172 |
Latr(1:3,3)=Lat_c |
173 |
B=1. |
174 |
! TO DO: replace by LAPACK |
175 |
CALL Gaussj(Latr,3,3,B,1,1) |
176 |
ELSE |
177 |
Latr=0. |
178 |
Latr(1,1)=1.d0 |
179 |
Latr(2,2)=1.d0 |
180 |
Latr(3,3)=1.d0 |
181 |
END IF |
182 |
|
183 |
! Actualization of Frozen using the FFFF... |
184 |
! Frozen has the advantage ie if given, it imposes _ALL_ the FFF flags. |
185 |
IF (Frozen(1).NE.0) THEN |
186 |
WRITE(IOOUT,*) "Frozen is given. Flags of the given POSCAR are overriden" |
187 |
FFF='T' |
188 |
|
189 |
NFroz=0 |
190 |
DO WHILE (Frozen(NFroz+1).NE.0) |
191 |
NFroz=NFroz+1 |
192 |
FFF(1:3,Frozen(NFroz))='F' |
193 |
END DO |
194 |
ELSE |
195 |
WRITE(IOOUT,*) "Frozen not given : using Flags of the given POSCAR" |
196 |
NFroz=0 |
197 |
Frozen=0 |
198 |
DO I=1,Nat |
199 |
IF ((FFF(1,I).EQ.'F').OR.(FFF(2,I).EQ.'F').OR.(FFF(3,I).EQ.'F')) THEN |
200 |
FFF(1:3,I)='F' |
201 |
NFroz=NFroz+1 |
202 |
Frozen(NFroz)=I |
203 |
END IF |
204 |
END DO |
205 |
WRITE(IOOUT,*) "Frozen atoms:",Frozen(1:NFroz) |
206 |
END IF |
207 |
|
208 |
IF (Vmd) THEN |
209 |
if (debug) WRITE(*,*) "DBG MAIN, L803, VMD=T,NbTypes,AtTypes",NbTypes,AtTypes(1:NbTypes) |
210 |
Line="" |
211 |
DO I=1,NbTypes |
212 |
Line=TRIM(Line) // " " // TRIM(AdjustL(AtTypes(I))) |
213 |
END DO |
214 |
Vasp_Title=Trim(Line) // " " // Trim(adjustL(Vasp_Title)) |
215 |
if (debug) WRITE(*,*) "DBG MAIN, L809, VMD=T, Vasp_Title=",TRIM(Vasp_Title) |
216 |
END IF |
217 |
|
218 |
if (debug) Call Header("Exiting ReadInput_Vasp") |
219 |
|
220 |
END SUBROUTINE READINPUT_VASP |
221 |
|