Statistiques
| Révision :

root / src / ReadGeom_vasp.f90

Historique | Voir | Annoter | Télécharger (12,22 ko)

1
SUBROUTINE ReadGeom_vasp
2

    
3
!----------------------------------------------------------------------
4
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon, 
5
!  Centre National de la Recherche Scientifique,
6
!  Université Claude Bernard Lyon 1. All rights reserved.
7
!
8
!  This work is registered with the Agency for the Protection of Programs 
9
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
10
!
11
!  Authors: P. Fleurat-Lessard, P. Dayal
12
!  Contact: optnpath@gmail.com
13
!
14
! This file is part of "Opt'n Path".
15
!
16
!  "Opt'n Path" is free software: you can redistribute it and/or modify
17
!  it under the terms of the GNU Affero General Public License as
18
!  published by the Free Software Foundation, either version 3 of the License,
19
!  or (at your option) any later version.
20
!
21
!  "Opt'n Path" is distributed in the hope that it will be useful,
22
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
23
!
24
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
25
!  GNU Affero General Public License for more details.
26
!
27
!  You should have received a copy of the GNU Affero General Public License
28
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
29
!
30
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
31
! for commercial licensing opportunities.
32
!----------------------------------------------------------------------
33

    
34
  Use Path_module
35
  Use Io_module
36

    
37
  IMPLICIT NONE
38

    
39

    
40
  CHARACTER(LCHARS) :: LineTmp,Line
41

    
42
  INTEGER(KINT), ALLOCATABLE :: NbAtType(:) !na
43
  INTEGER(KINT) :: NbType, NbTypeUser
44
  INTEGER(KINT) :: I, J, Iat, NAtP, Idx
45
  INTEGER(KINT) :: IGeom
46
  REAL(KREAL) :: Xt,Yt,Zt
47
  LOGICAL :: Debug, TChk
48
  CHARACTER(4), ALLOCATABLE :: FFFt(:,:) ! 3,Na
49
  LOGICAL, ALLOCATABLE :: FFFl(:,:) ! 3,Na
50

    
51
!!! for VASP inputs
52
! latx_loc used to check that the lattice parameters are the same for all geometries
53
  REAL(KREAL) :: lata_loc(3), latb_loc(3), latc_loc(3)
54
! VaspPar_loc is the local value of the vasp parametre
55
  REAL(KREAL) :: VaspPar_loc
56
! Vdir_loc is used to convert the read geometry to Cartesian.
57
! V_direct is set by the first geometry.
58
  CHARACTER(LCHARS) :: Vdir_loc
59

    
60

    
61
  INTERFACE
62
     function valid(string) result (isValid)
63
       CHARACTER(*), intent(in) :: string
64
       logical                  :: isValid
65
     END function VALID
66
  END INTERFACE
67

    
68
  debug=valid('Read_geom').or.valid('ReadGeom_vasp')
69

    
70
 if (debug) Call Header("Entering ReadGeom_vasp")
71

    
72
     ALLOCATE(FFF(3,nat),FFFl(3,Nat),FFFt(3,Nat))
73
     ! First geometry is a bit special for VASP as we have to set
74
     ! many things
75
     IGeom=1
76
     IF (DEBUG) WRITE(*,*) "Reading Geom :",IGeom
77
     READ(IOIN,'(A)') Vasp_Title
78
     READ(IOIN,*) Vasp_param
79

    
80
     READ(IOIN,*) Lat_a
81
     READ(IOIN,*) Lat_b
82
     READ(IOIN,*) Lat_c
83

    
84
     Lat_a=Lat_a*Vasp_param
85
     Lat_b=Lat_b*Vasp_param
86
     Lat_c=Lat_c*Vasp_param
87

    
88
     ALLOCATE(NbAtType(nat))
89
! PFL 2013.12.07 ->
90
! From VASP 5.3, POSCAR can have an additional line containing
91
! the names of the atoms
92
     VASP5=.FALSE.
93
     READ(IOIN,'(A)') Vasp_types
94
     LineTMp=AdjustL(Trim(Vasp_types))
95
     if (ICHAR(LineTmp(1:1))<48) THEN
96
        Call Warning("ReadGeom_Vasp","Illegal caracter found in reading Vasp types")
97
        STOP
98
     END IF
99
     If (ICHAR(LineTmp(1:1))>58) THEN
100
! we have a letter, the user has surely provided the names.
101
! We follow VASP and do not use them.
102
        VASP5=.TRUE.
103
        Vasp_types_user=Vasp_types
104
! we read the usual "number of atom by type" line
105
        READ(IOIN,'(A)') Vasp_types
106
     END IF
107
! <- PFL 2013.12.07     
108

    
109
     ! First, how many different types ?
110
     NbAtType=0
111
     READ(Vasp_types,*,END=999) NbAtType
112
999  CONTINUE
113
     NbType=0
114
     NatP=0
115
     DO WHILE (NbAtType(NbType+1).NE.0)
116
        NbType=NbType+1
117
        Natp=Natp+NbAtType(NbType)
118
     END DO
119

    
120

    
121
     if (NAtp.NE.Nat) THEN
122
        WRITE(IOOUT,*) 'WARNING Number of atoms not consistent between NAMELIST &path and First geom'
123
        WRITE(IOOUT,*) "Using:",Natp 
124
        DEALLOCATE(XyzGeomI, AtName)
125
        Nat=Natp 
126
        ALLOCATE(XyzGeomI(NGeomI,3,Nat), AtName(NAt))
127
     END if
128

    
129
     ! Do we know the atom types ?
130
     IF (AtTypes(1).EQ.'  ') THEN
131
        ! user has not provided atom types... we have to find them by ourselves
132
        ! by looking into the POTCAR file...
133
        INQUIRE(File="POTCAR", EXIST=Tchk)
134
        IF (.NOT.Tchk) THEN
135
           WRITE(*,*) "ERROR! No AtTypes provided, and POTCAR file not found"
136
           STOP
137
        END IF
138
        OPEN(IOTMP,File="POTCAR")
139
        DO I=1,NbType
140
           Line='Empty'
141
           DO WHILE (Line(1:5).NE.'TITEL')
142
              READ(IOTMP,'(A)') Line
143
              Line=AdjustL(Line)
144
           END DO
145
           Line=adjustl(Line(9:))
146
           Idx=index(Line," ")
147
           Line=adjustl(Line(Idx+1:))
148
           AtTypes(I)=Line(1:2)
149
        END DO
150
        if (debug) WRITE(*,'(A,100(1X,A2))') "ReadG:VASP AtTypes",AtTypes(1:NbType)
151
        CLOSE(IOTMP)
152

    
153
     ELSE  !AtTypes(1).EQ.'  '
154
        ! user has provided atom types
155
        NbTypeUser=0
156
        DO WHILE (AtTypes(NbTypeUser+1).NE.'  ')
157
           NbTypeUser=NbTypeUser+1
158
        END DO
159
        IF (NbType.NE.NbTypeUser) THEN
160
           WRITE(*,*) "ERROR Read_Geom : NbType in POSCAR do not match AtTypes"
161
           STOP
162
        END IF
163
     END IF
164

    
165
     IAt=1
166
     DO I=1,NbType
167
        DO J=1,NbAtType(I)
168
           AtName(Iat)=AtTypes(I)
169
           Iat=Iat+1
170
        END DO
171
     END DO
172
     DEALLOCATE(NbAtType)
173

    
174
     NbTypes=NbType
175
! PFL 2013.12.07 ->
176
! A comment: in fact, this line might just not be 'Selective Dynamics'
177
     READ(IOIN,'(A)') Vasp_comment
178
     LineTMp=AdjustL(Trim(Vasp_comment))
179
     Call upcase(LineTMP)
180
     if (LineTMP(1:1)=="S") THEN
181
        Vasp_SelectD=.TRUE.
182
        READ(IOIN,'(A)') Vasp_direct
183
     ELSE
184
        Vasp_SelectD=.FALSE.
185
        Vasp_direct=Vasp_comment
186
     END IF
187
! <- PFL 2013.12.07
188

    
189
     V_direct=adjustl(Vasp_direct)
190
     Call upcase(V_direct)
191

    
192
     if (debug) WRITE(*,*) "V_direct=",Trim(V_Direct)
193

    
194
     DO I=1,Nat
195
        IF (Vasp_SelectD) THEN
196
           READ(IOIN,*) XyzGeomI(IGeom,1:3,I),FFF(1:3,I)
197
           DO J=1,3
198
              FFF(J,I)=AdjustL(FFF(J,I))
199
              FFFl(j,i)=(FFF(j,i)(1:1).EQ.'T').OR.(FFF(j,i)(1:1).EQ.'t')
200
           END DO
201
        ELSE
202
           READ(IOIN,*) XyzGeomI(IGeom,1:3,I)
203
           FFFl(1:3,i)=.TRUE.
204
           FFF(1:3,i)="T"
205
        END IF
206
     END DO
207
! PFL 2013.12.07 ->
208
! Reading the VASP manual more carefully, it is stated:
209
! ! The seventh line (or eighth line if 'selective dynamics' is switched on)
210
! ! specifies whether the atomic positions are provided in cartesian coordinates
211
! ! or in direct coordinates (respectively fractional coordinates). As in the
212
! ! file KPOINTS only the first character on the line is significant and the
213
! ! only key characters recognized by VASP are 'C', 'c', 'K' or 'k' for
214
! ! switching to the cartesian mode.    
215
!
216
! We thus change V_direct to Direct if its first letter is not 'C' or 'K' 
217
! (we have it all in upper case)
218
     IF ((V_direct(1:1).NE.'C').AND.(V_direct(1:1).NE.'K')) THEN
219
        V_direct='DIRECT'
220
     END IF
221
! <- PFL 2013.12.07
222

    
223
     IF (V_direct(1:6).EQ.'DIRECT') THEN
224
        DO I=1,Nat
225
           Xt=XyzGeomI(IGeom,1,I)
226
           Yt=XyzGeomI(IGeom,2,I)
227
           Zt=XyzGeomI(IGeom,3,I)
228
           XyzGeomI(IGeom,1,I)=Xt*lat_a(1)+Yt*lat_b(1)+Zt*lat_c(1)
229
           XyzGeomI(IGeom,2,I)=Xt*lat_a(2)+Yt*lat_b(2)+Zt*lat_c(2)
230
           XyzGeomI(IGeom,3,I)=Xt*lat_a(3)+Yt*lat_b(3)+Zt*lat_c(3)
231
        END DO
232

    
233
     END IF
234

    
235
     ALLOCATE(X0_vasp(Nat),Y0_vasp(Nat),Z0_vasp(Nat))
236
     X0_vasp=XyzGeomI(IGeom,1,:)
237
     Y0_vasp=XyzGeomI(IGeom,2,:)
238
     Z0_vasp=XyzGeomI(IGeom,3,:)
239

    
240
     if (debug)  THEN
241
        WRITE(*,*) Nat
242
        WRITE(*,*) "Geom ",IGeom,"/",NGeomI
243
        DO I=1,Nat
244
           WRITE(*,'(1X,A2,3(1X,F15.6))') AtName(I),XyzGeomI(IGeom,1:3,I)
245
        END DO
246
     END IF
247

    
248

    
249
     DO IGeom=2,NGeomI
250
!!! PFL 16th March 2008 ->
251
! Users might want to use different conditions for different geometries
252
! i.e. to mix Cartesian and Direct :-p
253
! thus we check for each geom which condition is used.
254
! 
255
!! PFL 2013 Dec 07 ->
256
!!!!! For now we assume that all "POSCAR" used follow the same
257
!!!! pattern as the first one
258
!!! this has to be changed: reading the VASP header should be in
259
!!! a subroutine by itself and combined afterwards.
260
!!!! <- PFL 2013 Dec 07
261

    
262
! Title
263
        READ(IOIN,*) LineTmp
264
        !        if (debug) WRITE(*,*) "1 LineTmp:",Trim(LineTmp)
265
! Vasp_Param
266
        READ(IOIN,*) VaspPar_loc
267
        !        if (debug) WRITE(*,*) "2 LineTmp:",Trim(LineTmp)
268
! Lattice parameters
269
        READ(IOIN,*) Lata_loc 
270
        !        if (debug) WRITE(*,*) "3 LineTmp:",Trim(LineTmp)
271
        READ(IOIN,*) latb_loc
272
        !        if (debug) WRITE(*,*) "4 LineTmp:",Trim(LineTmp)
273
        READ(IOIN,*) Latc_loc
274
        !        if (debug) WRITE(*,*) "5 LineTmp:",Trim(LineTmp)
275
! PFL 2013 Dec 07 ->
276
! From VASP 5.3, POSCAR can have an additional line containing
277
! the names of the atoms
278
! Even thought VASP5 flag has been set on the first geometry,
279
! we are quite flexible and let the user mix old and new POSCAR:
280
        READ(IOIN,'(A)') LineTmp
281
        LineTMp=AdjustL(Trim(Vasp_types))
282
        if (ICHAR(LineTmp(1:1))<48) THEN
283
           Call Warning("ReadGeom_Vasp","Illegal caracter found in reading Vasp types")
284
           STOP
285
        END IF
286
        If (ICHAR(LineTmp(1:1))>58) THEN
287
! we have a letter, the user has surely provided the names.
288
! we read the usual "number of atom by type" line
289
           READ(IOIN,*) LineTmp
290
        !        if (debug) WRITE(*,*) "6 LineTmp:",Trim(LineTmp)
291
        END IF
292
! Do we have Selective Dynamics ?
293
        READ(IOIN,'(A)') Line
294
        LineTMp=AdjustL(Trim(Line))
295
        Call upcase(LineTMP)
296
        if (LineTMP(1:1)=="S") THEN
297
           if (.NOT.Vasp_SelectD) Vasp_comment=AdjustL(Line)
298
           Vasp_SelectD=.TRUE.
299
           READ(IOIN,'(A)') Vdir_loc
300
        ELSE
301
           Vasp_SelectD=.FALSE.
302
           Vdir_loc=Line
303
     END IF
304
! <- PFL 2013.12.07
305

    
306

    
307
! V_direct
308
        Vdir_loc=adjustl(Vdir_loc)
309
        Call upcase(Vdir_loc)
310
! PFL 2013.12.07 ->
311
     IF ((Vdir_loc(1:1).NE.'C').AND.(Vdir_loc(1:1).NE.'K')) THEN
312
        Vdir_loc='DIRECT'
313
     END IF
314
! <- PFL 2013.12.07
315

    
316

    
317
        !        if (debug) WRITE(*,*) "8 LineTmp:",Trim(LineTmp)
318

    
319
        Lata_loc=Lata_loc*VaspPar_loc-Lat_a
320
        if (dot_product(lata_loc,Lata_loc).GE.1e-6) THEN
321
           WRITE(*,*) "Lattice parameter a is different between geometries 1 and ",IGeom
322
           WRITE(IOOUT,*) "Lattice parameter a is different between geometries 1 and ",IGeom
323
           STOP
324
        END IF
325

    
326
        Latb_loc=Latb_loc*VaspPar_loc-Lat_b
327
        if (dot_product(latb_loc,Latb_loc).GE.1e-6) THEN
328
           WRITE(*,*) "Lattice parameter b is different between geometries 1 and ",IGeom
329
           WRITE(IOOUT,*) "Lattice parameter b is different between geometries 1 and ",IGeom
330
           STOP
331
        END IF
332

    
333
        Latc_loc=Latc_loc*VaspPar_loc-Lat_c
334
        if (dot_product(latc_loc,Latc_loc).GE.1e-6) THEN
335
           WRITE(*,*) "Lattice parameter c is different between geometries 1 and ",IGeom
336
           WRITE(IOOUT,*) "Lattice parameter c is different between geometries 1 and ",IGeom
337
           STOP
338
        END IF
339

    
340
        DO I=1,Nat
341
           IF (Vasp_SelectD) THEN
342
              READ(IOIN,*) XyzGeomI(IGeom,1:3,I),FFFt(1:3,I)
343
              DO J=1,3
344
! A frozen atom in any geom is considered frozen in all geom
345
                 FFFt(j,I)=AdjustL(FFFt(j,i))
346
                 FFFl(j,i)=FFFl(j,i).AND.(FFFt(j,i).EQ.'T')
347
              END DO
348
           ELSE
349
              READ(IOIN,*) XyzGeomI(IGeom,1:3,I)
350
           END IF
351

    
352
        END DO
353

    
354
        IF (Vdir_loc(1:6).EQ.'DIRECT') THEN
355
           DO I=1,Nat
356
              Xt=XyzGeomI(IGeom,1,I)
357
              Yt=XyzGeomI(IGeom,2,I)
358
              Zt=XyzGeomI(IGeom,3,I)
359
              XyzGeomI(IGeom,1,I)=Xt*lat_a(1)+Yt*lat_b(1)+Zt*lat_c(1)
360
              XyzGeomI(IGeom,2,I)=Xt*lat_a(2)+Yt*lat_b(2)+Zt*lat_c(2)
361
              XyzGeomI(IGeom,3,I)=Xt*lat_a(3)+Yt*lat_b(3)+Zt*lat_c(3)
362
           END DO
363
        END IF
364

    
365
        if (debug)  THEN
366
           WRITE(*,*) Nat
367
           WRITE(*,*) "Geom ",IGeom,"/",NGeomI
368
           DO I=1,Nat
369
              WRITE(*,'(1X,A2,3(1X,F15.6))') AtName(I),XyzGeomI(IGeom,1:3,I)
370
           END DO
371
        END IF
372

    
373
     END DO
374

    
375
     DO I=1,Nat
376
        DO J=1,3
377
           if (FFFl(j,i)) FFF(j,i)="T"
378
        END DO
379
     END DO
380

    
381
 Deallocate(FFFl,FFFt)
382

    
383

    
384
  if (debug) Call Header("Exiting ReadGeom_vasp")
385

    
386
END SUBROUTINE ReadGeom_vasp