Statistiques
| Révision :

root / src / ReadInput_siesta.f90

Historique | Voir | Annoter | Télécharger (17,97 ko)

1
 SUBROUTINE ReadInput_siesta
2

    
3
! This routine reads an input template for Siesta
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
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
43
!
44
  INTERFACE
45
!
46
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
47

    
48
     function valid(string) result (isValid)
49
       CHARACTER(*), intent(in) :: string
50
       logical                  :: isValid
51
     END function VALID
52

    
53
    FUNCTION SearchInput(Input,String,Line,Clean)  Result (Found)
54

    
55
      Use Vartypes
56
      use io_module
57
! Input
58
      TYPE (Input_line), POINTER, INTENT(IN) :: Input
59
      CHARACTER(*), INTENT(IN) :: String
60
      CHARACTER(*), OPTIONAL, INTENT(IN) :: Clean
61

    
62
! Output
63
      TYPE (Input_line), POINTER, INTENT(OUT) :: Line
64

    
65
      LOGICAL :: Found
66

    
67
    END FUNCTION SearchInput
68

    
69
    FUNCTION InString(Line,String,Case,Clean,Back)  Result(Pos)
70

    
71
      Use VarTypes
72

    
73
      implicit none
74
! Input
75
      CHARACTER(*), INTENT(IN) :: Line
76
      CHARACTER(*), INTENT(IN) :: String
77
      LOGICAL, OPTIONAL, INTENT(IN) :: Case
78
      LOGICAL, OPTIONAL, INTENT(IN) :: Back
79
      CHARACTER(*), OPTIONAL, INTENT(IN) :: Clean
80

    
81
! Output
82
! the position of String in Line (the first one) unless Back is present
83
      INTEGER(KINT) :: Pos
84
    END FUNCTION InString
85

    
86
    SUBROUTINE die(routine, msg, file, line, unit)
87

    
88
      Use VarTypes
89
      Use io_module
90

    
91
      implicit none
92
!--------------------------------------------------------------- Input Variables
93
      character(len=*), intent(in)           :: routine, msg
94
      character(len=*), intent(in), optional :: file
95
      integer(KINT), intent(in), optional      :: line, unit
96

    
97
    END SUBROUTINE die
98

    
99
    SUBROUTINE Warning(routine, msg, file, line, unit)
100

    
101
      Use VarTypes
102
      Use io_module
103

    
104
      implicit none
105

    
106
      character(len=*), intent(in)           :: routine, msg
107
      character(len=*), intent(in), optional :: file
108
      integer(KINT), intent(in), optional      :: line, unit
109

    
110
    END SUBROUTINE Warning
111

    
112

    
113
 SUBROUTINE WriteList(Input,Unit)
114

    
115
! This routine reads an input template for Siesta
116

    
117
  use VarTypes
118
  use Io_module
119

    
120
  IMPLICIT NONE
121

    
122
! Input
123
      TYPE (Input_line), POINTER, INTENT(IN) :: Input
124
      INTEGER(KINT), OPTIONAL, INTENT(IN) :: Unit
125

    
126
    END SUBROUTINE WriteList
127

    
128
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
129
!
130
 END  INTERFACE
131
!
132
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
133

    
134

    
135
  CHARACTER(132) ::  Line,Line2
136
  INTEGER(KINT) ::  Idx,LineL
137
  INTEGER(KINT) ::  IAt,I
138
  INTEGER(KINT) :: IoRead, ITmp
139
  REAL(KREAL) :: B(3),Xtmp, Ytmp, Ztmp
140
  REAL(KREAL) :: Lata,Latb,Latc,Alpha,Beta,Gamma
141
  REAL(KREAL), ALLOCATABLE :: GeomCartTmp(:,:) ! (Nat,3)
142
  REAL(KREAL) :: LatLoc(3,3)
143
  
144
  LOGICAL :: Debug
145
  LOGICAL :: FSpecies, FCoord
146

    
147
  TYPE(Input_Line), POINTER :: Search,Bla
148

    
149
  Debug=Valid("readinput").OR.Valid("readinput_siesta")
150

    
151
 if (debug) Call Header("Entering ReadInput_Siesta")
152

    
153
  ! We read the Siesta input file
154

    
155
     ALLOCATE(Siesta_Input)
156
     NULLIFY(Siesta_Input%next)
157
     NULLIFY(Siesta_Input%prev)
158
     Current => Siesta_Input
159

    
160
     FSpecies=.FALSE.
161
     FCoord=.FALSE.
162

    
163
     READ(IOIN,'(A)',iostat=IoRead) Line
164

    
165
     DO WHILE (IoRead==0)
166
        Line=AdjustL(Line)
167
        if (debug) WRITE(*,*) 'Line:', Line
168
        current%Line=TRIM(Line)
169
        ALLOCATE(current%next)
170
        Current%next%prev => Current
171
        Current => Current%next
172
        current%line="toto"
173
        Nullify(Current%next)
174

    
175
        READ(IOIN,'(A)',iostat=IoRead) Line
176
     END DO
177
! With this procedure, the last current is not valid and should be deleted.
178
       Bla => Current%prev
179
       nullify(Bla%next)
180
       deallocate(Current)
181
       current => Bla
182

    
183
     if (debug) THEN
184
        WRITE(*,*) 'Input just read'
185
        Call WriteList(Siesta_input,Unit=IOOUT)
186
     END IF
187

    
188
! We analyse the input
189

    
190
! We look for the NumberofAtoms
191
     If (SearchInput(Siesta_Input,"NUMBEROFATOMS",Search,Clean=".-_")) THEN
192
        Line=AdjustL(Search%line)
193
        Idx=Index(Line," ")
194
        Line2=Trim(AdjustL(Line(Idx+1:)))
195
        Read(Line2,*) IAt
196
        if (Iat/=Nat) THEN
197
           Call Die('ReadInput_siesta','Nat in FDF sample different from  Nat Path input', Unit=IOOUT)
198
        END IF
199
     ELSE
200
! There is no atom number defined !!!
201
           Call Warning('ReadInput_siesta','No NumberOfAtoms in FDF sample', Unit=IOOUT)
202
           WRITE(current%Line,'(1X,"NumberOfAtoms ",I5)') Nat
203
           ALLOCATE(current%next)
204
           Current%next%prev => Current
205
           Current => Current%next
206
           Nullify(Current%next)
207
         
208
        END IF
209

    
210
! We look for the NumberofSpecies
211
        IF (SearchInput(Siesta_Input,"NUMBEROFSPECIES",Search,Clean=".-_")) THEN
212
           Line=AdjustL(Search%line)
213
           Idx=Index(Line," ")
214
           Line2=Trim(AdjustL(Line(Idx+1:)))
215
           Read(Line2,*) Siesta_NbSpecies
216
           ALLOCATE(Siesta_SpeciesMass(Siesta_NbSpecies))
217
           ALLOCATE(Siesta_SpeciesName(Siesta_NbSpecies))
218
        END IF
219

    
220
! We look for SystemLabel
221
        If (SearchInput(Siesta_Input,"SYSTEMLABEL",Search,Clean=".-_")) THEN
222
           Line=AdjustL(Search%line)
223
           Idx=Index(Line," ")
224
           Siesta_Label=Trim(adjustl(Line(Idx+1:)))
225
        ELSE
226
           Siesta_label='siesta'
227
        END IF
228

    
229
! We look for the ChemicalSpeciesLabel block
230
        IF (SearchInput(Siesta_Input,"CHEMICALSPECIESLABEL",Search,Clean=".-_")) THEN
231
           if (.NOT.ALLOCATED(IdxSpecies)) ALLOCATE(IdxSpecies(NAt))
232
           I=0
233
           Search => Search%next
234
           DO WHILE (InString(Search%line,'ENDBLOCK',Case=.FALSE.,Clean=".-_")==0)
235
              I=I+1
236
              if (I>Siesta_NbSpecies) THEN
237
                 Call Die('ReadInput_siesta:Reading ChemicalSpeciesLabel','Found more line in this block than NbSpecies !')
238
              END IF
239
              Line=AdjustL(Search%Line)
240
              Read(Line,*) ITmp
241
              Idx=Index(Line,' ')
242
              Line=AdjustL(Line(Idx+1:))
243
              Read(Line,*) Idx
244
              Siesta_SpeciesMass(ITmp)=Idx
245
              Idx=Index(Line,' ')
246
              Line=AdjustL(Line(Idx+1:))
247
              Idx=Index(Line,' ')
248
              Siesta_SpeciesName(ITmp)=Line(1:Idx-1)
249
              Search => Search%next
250
           END DO
251
           IF (I/=Siesta_NbSpecies) Call Die('ReadInput_siesta:Reading ChemicalSpeciesLabel', &
252
                'Number of lines in this block different from NbSpecies')
253
        ELSE
254
           Call Die('ReadInput_siesta:Reading ChemicalSpeciesLabel', &
255
                'Block ChemicalSpeciesLabel is mandatory !')
256
        END IF
257

    
258

    
259
! We look for the AtomicCoordinatesAndAtomicSpecies  block
260
        IF (SearchInput(Siesta_Input,"ATOMICCOORDINATESANDATOMICSPECIES",Search,Clean=".-_")) THEN
261
           ALLOCATE(Siesta_Paste(Nat))
262
           Current=>Search
263
           DO I=1,NAt
264
              Search => Search%next
265
              Read(Search%line,*) XTmp,YTmp,ZTmp,IdxSpecies(I)
266
! We give a name to this atom
267
              IF (AtName(I)/="") THEN
268
!                    Write(Line,'(A,I5,1X,A2,1X,A32)') 'AtName & SpeciesName for atom ',I,AtName(I), &
269
!                         TRIM(Siesta_SpeciesName(IdxSpecies(I)))
270
!                    WRITE(*,'(1X,A)') Line
271
                 If (InString(Atname(I),TRIM(Siesta_SpeciesName(IdxSpecies(I))))==0) THEN
272
                    Write(Line,'(A,I5,1X,A2,1X,A32)') 'AtName /= SpeciesName for atom ',I,AtName(I), &
273
                         TRIM(Siesta_SpeciesName(IdxSpecies(I)))
274
                    Call Die('Readinput_siesta:Reading AtomicCoordinatesAndAtomicSpecies',Line,Unit=IOOUT)
275
                 END IF
276
! We look for the Mass number also
277
                 IF (Atome(I)/=Siesta_SpeciesMass(IdxSpecies(I))) THEN
278
                    Write(Line,'(A,I5,1X,I5,1X,I5)') 'AtMass /= SpeciesMass for atom ',I,Atome(I), &
279
                         Siesta_SpeciesMass(IdxSpecies(I))
280
                    Call Die('ReadInput_siesta:Reading AtomicCoordinatesAndAtomicSpecies',Line,Unit=IOOUT)
281
                 END IF
282
              ELSE
283
                 AtName(I)=AdjustL(Trim(Siesta_SpeciesName(IdxSpecies(I))))
284
                 Atome(I)=Siesta_SpeciesMass(IdxSpecies(I))
285
              END IF
286
! we look for something else at the end of the line
287
! We save everything but the x,y,z, and species description              
288
              Line=AdjustL(search%line)
289
! We skip x
290
              Idx=Index(Line,' ')
291
              Line=AdjustL(Line(Idx+1:))
292
! we skip y
293
              Idx=Index(Line,' ')
294
              Line=AdjustL(Line(Idx+1:))
295
! we skip z
296
              Idx=Index(Line,' ')
297
              Line=AdjustL(Line(Idx+1:))
298
! we skip species
299
              Idx=Index(Line,' ')
300
              Line=AdjustL(Line(Idx+1:))
301
              Siesta_Paste(I)=TRIM(Line)
302
           END DO
303
           if (debug) THEN
304
              WRITE(*,*) 'Input before deletion of coord block'
305
              Call WriteList(Siesta_input)
306
           END IF
307
! We will now delete this block from our input sample as it will then be
308
! written directly by Opt'n Path
309
! Search%next point on %endblock
310
           search => search%next
311
           IF (ASSOCIATED(Search%next)) THEN
312
! we are not at the end of the input file
313
              if (ASSOCIATED(Current%Prev)) THEN
314
                 Search%next%prev => current%prev
315
                 current%prev%next => search%next
316
              ELSE
317
! the coordinate block is at the begining of the input
318
                 siesta_input => Search%next
319
                 Nullify(Siesta_Input%Prev)
320
              END IF
321
           ELSE
322
! the coordinate block is the last part of the input
323
              nullify(current%prev%next)
324
           END IF
325
           if (debug) THEN
326
              WRITE(*,*) 'Input after deletion of coord block 1'
327
              Call WriteList(Siesta_input)
328
           END IF
329

    
330
           DO I=1,Nat+2
331
              bla=>current
332
              current=> current%next
333
              deallocate(bla)
334
           END DO
335
           if (debug) THEN
336
              WRITE(*,*) 'Input after deletion of coord block 2'
337
              Call WriteList(Siesta_input)
338
           END IF
339
        ELSE
340
           IF (SearchInput(Siesta_Input,"ZMATRIX",Search,Clean=".-_")) THEN
341
              call Die('ReadInput_Siesta','For now, I need the full block'//&
342
                   'AtomicCoordinatesAndAtomicSpecies, ZMatrix not yet handled.')
343
           ELSE
344
              call Die('ReadInput_Siesta','For now, I need the full block' //&
345
              'AtomicCoordinatesAndAtomicSpecies.')
346
           END IF
347
        END IF
348

    
349
        IF (SearchInput(Siesta_Input,"LATTICE",Search,Clean=".-_")) THEN
350
! This is a pbc calculation
351
           FPBC=.TRUE.
352
           IPer=3
353
           Kabeg=-1
354
           kaEnd=1
355
           kbBeg=-1
356
           kbEnd=1
357
           kcBeg=-1
358
           kcEnd=1
359
         
360

    
361
         IF (SearchInput(Siesta_Input,"LATTICECONSTANT",Search,Clean=".-_")) THEN
362
           Line=Adjustl(Search%Line)
363
! We discar the label
364
           Idx=Index(Line,' ')
365
           Line=AdjustL(Line(Idx+1:))
366
! we read the value
367
           Read(Line,*) Siesta_LatticeConstant
368
! We discard the value
369
           Idx=Index(Line,' ')
370
           Line=AdjustL(Line(Idx+1:))
371
           LineL=Len_Trim(Line)
372
! We read the unit
373
           If (LineL>0) THEN
374
              Call UpCase(Line)
375
              SELECT CASE (Line) 
376
                CASE ('ANG')
377
                   Siesta_Lat_Unit=1.d0
378
                CASE ('BOHR')
379
                   Siesta_Lat_Unit=a0
380
              END SELECT
381
           ELSE
382
              Siesta_Lat_Unit=1.d0
383
           END IF
384
         ELSE
385
! We have no LatticeConstant but we need one for our calculation
386
            Siesta_LatticeConstant=1.
387
            Siesta_Lat_Unit=1.d0
388
         END IF
389

    
390
         IF (SearchInput(Siesta_Input,"LATTICEVECTORS",Search,Clean=".-_")) THEN
391
           search => search%next
392
           Line=Adjustl(Search%Line)
393
           Read(Line,*) Lat_a(1:3)
394
           search => search%next
395
           Line=Adjustl(Search%Line)
396
           Read(Line,*) Lat_b(1:3)
397
           search => search%next
398
           Line=Adjustl(Search%Line)
399
           Read(Line,*) Lat_c(1:3)
400

    
401
         ELSEIF (SearchInput(Siesta_Input,"LATTICEPARAMETERS",Search,Clean=".-_")) THEN
402
           search => search%next
403
           Line=Adjustl(Search%Line)
404
           Read(Line,*) Lata,Latb,Latc,Alpha,Beta,Gamma
405

    
406
            Lat_a=0.
407
            Lat_b=0.
408
            Lat_c=0.
409
            Lat_a(1)=Lata
410
            Lat_b(1)=LatB*cos(Gamma*Pi/180d0)
411
            Lat_b(2)=LatB*sin(Gamma*Pi/180d0)
412
            Lat_c(1)=Latc*cos(Beta*Pi/180.)
413
            Lat_c(2)=(Latb*Latc*cos(Alpha*Pi/180.)-Lat_b(1)*Lat_c(1))/Lat_b(2)
414
            Lat_c(3)=sqrt(Latc*Latc-Lat_c(1)**2-Lat_c(2)**2)
415
         ELSE
416
! We have a lattice constant but nothing else. We issue a warning just in case,
417
! and we take the defaut values 1. 1. 1. 90. 90. 90.
418
            Line="LatticeConstant found, but not LatticeVectors nor LatticeParameters. Taking 1. 1. 1. 90. 90. 90."
419
            Call Warning("ReadInput_siesta",Line)
420
            Lat_a=(/1.,0.,0./)
421
            Lat_b=(/0.,1.,0./)
422
            Lat_c=(/0.,0.,1./)
423
         END IF
424

    
425
         IF (debug) THEN 
426
            WRITE(*,*) "Lattice vectors before scaling with LatticeConstant"
427
            WRITE(*,'(1X,A,3(1X,F10.6))')   "Lat_a",Lat_a
428
            WRITE(*,'(1X,A,3(1X,F10.6))')   "Lat_b",Lat_b
429
            WRITE(*,'(1X,A,3(1X,F10.6))')   "Lat_c",Lat_c
430
         END IF
431
           Lat_a=Lat_a*Siesta_LatticeConstant*Siesta_Lat_Unit
432
           Lat_b=Lat_b*Siesta_LatticeConstant*Siesta_Lat_Unit
433
           Lat_c=Lat_c*Siesta_LatticeConstant*Siesta_Lat_Unit
434

    
435
         IF (debug) THEN 
436
            WRITE(*,*) "Lattice vectors After scaling with LatticeConstant"
437
            WRITE(*,'(1X,A,3(1X,F10.6))')   "Lat_a",Lat_a
438
            WRITE(*,'(1X,A,3(1X,F10.6))')   "Lat_b",Lat_b
439
            WRITE(*,'(1X,A,3(1X,F10.6))')   "Lat_c",Lat_c
440
         END IF
441

    
442
      END IF
443

    
444
         IF (SearchInput(Siesta_Input,"ATOMICCOORDINATESFORMAT",Search,Clean=".-_")) THEN
445
           Line=Adjustl(Search%Line)
446
           Idx=Index(Line,' ')
447
           Line=AdjustL(Line(Idx+1:))
448
           Call UpCase(Line)
449
           SELECT CASE (Line) 
450
              CASE ('ANG','NOTSCALEDCARTESIANANG')
451
                 Siesta_Unit_Read=1.d0
452
              CASE ('FRACTIONAL','SCALEDBYLATTICEVECTORS')
453
                 IF (FPBC) THEN
454
                    Siesta_Unit_Read=1.d0
455
                    V_DIRECT="DIRECT"
456
                    Latr(1:3,1)=Lat_a
457
                    Latr(1:3,2)=Lat_b
458
                    Latr(1:3,3)=Lat_c
459
                    B=1.
460
! TO DO: replace by LAPACK
461
                    CALL Gaussj(Latr,3,3,B,1,1)
462
                    LatLoc(1:3,1)=Lat_a
463
                    LatLoc(1:3,2)=Lat_b
464
                    LatLoc(1:3,3)=Lat_c
465
                    Allocate(GeomCartTmp(Nat,3))
466
                    Do I=1,NGeomI
467
                       GeomCartTmp=Reshape(XyzGeomI(I,1:3,1:Nat),(/Nat,3/),ORDER=(/2,1/))
468
! TO DO: shall we replace MatMull by DGEMM ?
469
                       XyzGeomI(I,1:3,1:Nat)=Reshape(MatMul(GeomCartTmp,Latloc),(/3,Nat/),ORDER=(/2,1/))
470
                   END DO
471
                 ELSE
472
                    WRITE(Line2,*) "AtomicCoordinatesFormat=" // Trim(Line) &
473
               //", but there is no information about Lattice parameters"
474
                    Call Die("ReadInput_siesta",Line2)
475
                 END IF
476
              CASE ('BOHR','NOTSCALEDCARTESIANBOHR')
477
                 Siesta_Unit_Read=a0
478
                 IF (INPUT=='SIESTA') THEN
479
! We have read the coordinates, but not the unit. This is corrected here
480
                    XyZGeomI=XyzGeomI*a0
481
                 END IF
482
              CASE ('SCALEDCARTESIAN')
483
                 Siesta_Unit_Read=Siesta_LatticeConstant
484
                 If (INPUT=='SIESTA') THEN
485
                    XyzGeomI=XyzGeomI*Siesta_Unit_Read
486
                 END IF
487
            END SELECT
488
         ELSE
489
            Siesta_Unit_Read=1.d0
490
         END IF
491

    
492
        IF (SearchInput(Siesta_Input,"ATOMICCOORFORMATOUT",Search,Clean=".-_")) THEN
493
           Line=Adjustl(Search%Line)
494
           Idx=Index(Line,' ')
495
           Line=AdjustL(Line(Idx+1:))
496
           Call UpCase(Line)
497
           SELECT CASE (Line) 
498
              CASE ('ANG','NOTSCALEDCARTESIANANG')
499
                 Siesta_Unit_Write=1.d0
500
              CASE ('FRACTIONAL','SCALEDBYLATTICEVECTORS')
501
                 Siesta_Unit_Write=1.d0
502
                 V_DIRECT_Write='DIRECT'
503
              CASE ('BOHR','NOTSCALEDCARTESIANBOHR')
504
                 Siesta_Unit_Write=Unit ! 1/a0
505
            END SELECT
506
         END IF
507
         IF (SearchInput(Siesta_Input,"SUPERCELL",Search,Clean=".-_")) THEN
508
            Line=Adjustl(search%line)
509
            Call Upcase(Line)
510
            Call CleanString(Line,".-_")
511
            If (Index(Line,"%BLOCK")/=0) THEN
512
               Call Die('ReadInput_siesta:SuperCell',"SuperCell  NOT possible in Opt'n Path")
513
            END IF
514
         END IF
515

    
516
!         Call Die('Readinput_siesta:fin',' Lecture finie')
517

    
518
     if (debug) Call Header("Exiting ReadInput_Siesta")
519

    
520
   END SUBROUTINE READINPUT_SIESTA