Statistiques
| Révision :

root / src / Write_vasp.f90

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

1 1 pfleura2
SUBROUTINE Write_vasp(poscar)
2 12 pfleura2
!----------------------------------------------------------------------
3 12 pfleura2
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon,
4 12 pfleura2
!  Centre National de la Recherche Scientifique,
5 12 pfleura2
!  Université Claude Bernard Lyon 1. All rights reserved.
6 12 pfleura2
!
7 12 pfleura2
!  This work is registered with the Agency for the Protection of Programs
8 12 pfleura2
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
9 12 pfleura2
!
10 12 pfleura2
!  Authors: P. Fleurat-Lessard, P. Dayal
11 12 pfleura2
!  Contact: optnpath@gmail.com
12 12 pfleura2
!
13 12 pfleura2
! This file is part of "Opt'n Path".
14 12 pfleura2
!
15 12 pfleura2
!  "Opt'n Path" is free software: you can redistribute it and/or modify
16 12 pfleura2
!  it under the terms of the GNU Affero General Public License as
17 12 pfleura2
!  published by the Free Software Foundation, either version 3 of the License,
18 12 pfleura2
!  or (at your option) any later version.
19 12 pfleura2
!
20 12 pfleura2
!  "Opt'n Path" is distributed in the hope that it will be useful,
21 12 pfleura2
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
22 12 pfleura2
!
23 12 pfleura2
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
24 12 pfleura2
!  GNU Affero General Public License for more details.
25 12 pfleura2
!
26 12 pfleura2
!  You should have received a copy of the GNU Affero General Public License
27 12 pfleura2
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
28 12 pfleura2
!
29 12 pfleura2
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
30 12 pfleura2
! for commercial licensing opportunities.
31 12 pfleura2
!----------------------------------------------------------------------
32 1 pfleura2
33 5 pfleura2
  Use Path_module, only : Nat, NGeomF,XyzGeomF,intCoordF,Coord,FrozAtoms,IndZmat,LatR,Ncoord, Vmd
34 1 pfleura2
  Use Io_module
35 1 pfleura2
36 1 pfleura2
  IMPLICIT NONE
37 1 pfleura2
38 1 pfleura2
  CHARACTER(SCHARS), INTENT(IN) :: poscar
39 1 pfleura2
40 2 pfleura2
  INTEGER(KINT) :: IGeom, Idx
41 1 pfleura2
  REAL(KREAL), ALLOCATABLE :: GeomTmpC(:), GeomTmp(:)
42 1 pfleura2
  CHARACTER(SCHARS) :: Line,Line2
43 1 pfleura2
44 1 pfleura2
  ! For VMD printing
45 1 pfleura2
  CHARACTER(SCHARS), PARAMETER :: FirstWord="mol "
46 1 pfleura2
  CHARACTER(LCHARS), PARAMETER :: LastWords=" type POSCAR first 0 last -1 step 1 filebonds 1 autobonds 1 waitfor all"
47 1 pfleura2
48 1 pfleura2
  CHARACTER(LCHARS) :: TITLE
49 1 pfleura2
  LOGICAL :: Debug
50 1 pfleura2
51 1 pfleura2
  INTERFACE
52 1 pfleura2
     function valid(string) result (isValid)
53 1 pfleura2
       CHARACTER(*), intent(in) :: string
54 1 pfleura2
       logical                  :: isValid
55 1 pfleura2
     END function VALID
56 1 pfleura2
  END INTERFACE
57 1 pfleura2
58 1 pfleura2
  debug=valid('write_vasp')
59 1 pfleura2
  if (debug) WRITE(*,*) '================ Entering Write_VASP ===================='
60 1 pfleura2
61 1 pfleura2
  ALLOCATE(GeomTmpC(3*Nat), GeomTmp(NCoord))
62 1 pfleura2
63 1 pfleura2
  Line2="00"
64 1 pfleura2
  DO IGeom=1,NGeomF
65 1 pfleura2
     WRITE(Line,'(I5)') IGeom-1
66 1 pfleura2
     Idx=2-Len_TRIM(ADJUSTL(Line))
67 1 pfleura2
     OPEN(IOTMP,File=TRIM(POSCAR) // "_" // Line2(1:Idx) // AdjustL(TRIM(Line)))
68 1 pfleura2
     ! we convert the coordinates into Cartesian coordinates
69 1 pfleura2
     SELECT CASE (Coord)
70 1 pfleura2
     CASE ('CART','HYBRID')
71 1 pfleura2
        GeomTmpC=Reshape(reshape(XyzGeomF(IGeom,:,:),(/Nat,3/),ORDER=(/2,1/)),(/3*Nat/))
72 1 pfleura2
     CASE ('ZMAT')
73 1 pfleura2
        GeomTmp=IntCoordF(IGeom,:)
74 1 pfleura2
        ! we have to generate the cartesian coordinates from the internal coordinates
75 1 pfleura2
        CAll Int2Cart(nat,indzmat,geomtmp,GeomTmpC)
76 1 pfleura2
     CASE ('MIXED')
77 1 pfleura2
        GeomTmp=IntCoordF(IGeom,:)
78 1 pfleura2
        CAll Mixed2Cart(nat,indzmat,geomtmp,GeomTmpC)
79 1 pfleura2
     END SELECT
80 1 pfleura2
81 1 pfleura2
     if (debug) WRITE(*,*) "Converting geom ",IGeom," into file ",Trim(POSCAR) // "_" // Line2(1:Idx) // AdjustL(TRIM(Line))
82 1 pfleura2
83 1 pfleura2
     WRITE(Title,'(A,I2,"/",I2)') Trim(Vasp_Title) // " - Geom ",IGeom-1,NGeomF-1
84 1 pfleura2
85 1 pfleura2
     Call PrintGeomVasp(Title,geomTmpC,Latr,FrozAtoms,IoTmp)
86 1 pfleura2
87 1 pfleura2
     CLOSE(IOTMP)
88 1 pfleura2
  END DO
89 1 pfleura2
90 1 pfleura2
  if (Vmd) THEN
91 1 pfleura2
     WRITE(IOOUT,*) "## Insert the following list into the Test_NEB_example.vmd file for an easy VMD use"
92 1 pfleura2
93 1 pfleura2
     Line2="00"
94 1 pfleura2
     WRITE(IOOUT,'(A)') TRIM(FirstWord) // " new " // TRIM(POSCAR) // "_00" // TRIM(LastWords)
95 1 pfleura2
     DO IGeom=2,NGeomF
96 1 pfleura2
        WRITE(Line,'(I5)') IGeom-1
97 1 pfleura2
        Idx=2-Len_TRIM(ADJUSTL(Line))
98 1 pfleura2
        WRITE(IOOUT,'(A)') TRIM(FirstWord) // " addfile " // TRIM(POSCAR) //  &
99 1 pfleura2
             "_" // Line2(1:Idx) // TRIM(ADJUSTL(Line)) // TRIM(LastWords)
100 1 pfleura2
     END DO
101 1 pfleura2
     WRITE(IOOUT,*) "## End of List"
102 1 pfleura2
  END IF
103 1 pfleura2
104 1 pfleura2
  if (debug) WRITE(*,*) '================  Write_VASP OVER ===================='
105 1 pfleura2
  DeALLOCATE(GeomTmpC, GeomTmp)
106 1 pfleura2
107 1 pfleura2
END SUBROUTINE Write_vasp