Statistiques
| Révision :

root / src / Write_vasp.f90

Historique | Voir | Annoter | Télécharger (3,83 ko)

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

    
33
  Use Path_module, only : Nat, NGeomF,XyzGeomF,intCoordF,Coord,FrozAtoms,IndZmat,LatR,Ncoord, Vmd
34
  Use Io_module
35

    
36
  IMPLICIT NONE
37

    
38
  CHARACTER(SCHARS), INTENT(IN) :: poscar
39

    
40
  INTEGER(KINT) :: IGeom, Idx
41
  REAL(KREAL), ALLOCATABLE :: GeomTmpC(:), GeomTmp(:)
42
  CHARACTER(SCHARS) :: Line,Line2
43

    
44
  ! For VMD printing
45
  CHARACTER(SCHARS), PARAMETER :: FirstWord="mol "
46
  CHARACTER(LCHARS), PARAMETER :: LastWords=" type POSCAR first 0 last -1 step 1 filebonds 1 autobonds 1 waitfor all"
47

    
48
  CHARACTER(LCHARS) :: TITLE
49
  LOGICAL :: Debug
50

    
51
  INTERFACE
52
     function valid(string) result (isValid)
53
       CHARACTER(*), intent(in) :: string
54
       logical                  :: isValid
55
     END function VALID
56
  END INTERFACE
57

    
58
  debug=valid('write_vasp')
59
  if (debug) WRITE(*,*) '================ Entering Write_VASP ===================='
60

    
61
  ALLOCATE(GeomTmpC(3*Nat), GeomTmp(NCoord))
62

    
63
  Line2="00"
64
  DO IGeom=1,NGeomF
65
     WRITE(Line,'(I5)') IGeom-1
66
     Idx=2-Len_TRIM(ADJUSTL(Line))
67
     OPEN(IOTMP,File=TRIM(POSCAR) // "_" // Line2(1:Idx) // AdjustL(TRIM(Line)))
68
     ! we convert the coordinates into Cartesian coordinates
69
     SELECT CASE (Coord)
70
     CASE ('CART','HYBRID')
71
        GeomTmpC=Reshape(reshape(XyzGeomF(IGeom,:,:),(/Nat,3/),ORDER=(/2,1/)),(/3*Nat/))
72
     CASE ('ZMAT')
73
        GeomTmp=IntCoordF(IGeom,:)
74
        ! we have to generate the cartesian coordinates from the internal coordinates
75
        CAll Int2Cart(nat,indzmat,geomtmp,GeomTmpC)
76
     CASE ('MIXED')
77
        GeomTmp=IntCoordF(IGeom,:)
78
        CAll Mixed2Cart(nat,indzmat,geomtmp,GeomTmpC)
79
     END SELECT
80

    
81
     if (debug) WRITE(*,*) "Converting geom ",IGeom," into file ",Trim(POSCAR) // "_" // Line2(1:Idx) // AdjustL(TRIM(Line))
82

    
83
     WRITE(Title,'(A,I2,"/",I2)') Trim(Vasp_Title) // " - Geom ",IGeom-1,NGeomF-1
84

    
85
     Call PrintGeomVasp(Title,geomTmpC,Latr,FrozAtoms,IoTmp)
86

    
87
     CLOSE(IOTMP)
88
  END DO
89

    
90
  if (Vmd) THEN
91
     WRITE(IOOUT,*) "## Insert the following list into the Test_NEB_example.vmd file for an easy VMD use"
92

    
93
     Line2="00"
94
     WRITE(IOOUT,'(A)') TRIM(FirstWord) // " new " // TRIM(POSCAR) // "_00" // TRIM(LastWords)
95
     DO IGeom=2,NGeomF
96
        WRITE(Line,'(I5)') IGeom-1
97
        Idx=2-Len_TRIM(ADJUSTL(Line))
98
        WRITE(IOOUT,'(A)') TRIM(FirstWord) // " addfile " // TRIM(POSCAR) //  &
99
             "_" // Line2(1:Idx) // TRIM(ADJUSTL(Line)) // TRIM(LastWords)
100
     END DO
101
     WRITE(IOOUT,*) "## End of List"
102
  END IF
103

    
104
  if (debug) WRITE(*,*) '================  Write_VASP OVER ===================='
105
  DeALLOCATE(GeomTmpC, GeomTmp)
106

    
107
END SUBROUTINE Write_vasp