Statistiques
| Révision :

root / src / Write_vasp.f90 @ 2

Historique | Voir | Annoter | Télécharger (2,52 ko)

1
SUBROUTINE Write_vasp(poscar)
2

    
3
  Use Path_module
4
  Use Io_module
5

    
6
  IMPLICIT NONE
7

    
8
  CHARACTER(SCHARS), INTENT(IN) :: poscar
9

    
10
  INTEGER(KINT) :: IGeom, Idx, Iat, I,J,NFr
11
  REAL(KREAL), ALLOCATABLE :: GeomTmpC(:), GeomTmp(:)
12
  REAL(KREAL) :: MRot(3,3), Rmsd
13
  CHARACTER(SCHARS) :: Line,Line2
14

    
15
  ! For VMD printing
16
  CHARACTER(SCHARS), PARAMETER :: FirstWord="mol "
17
  CHARACTER(LCHARS), PARAMETER :: LastWords=" type POSCAR first 0 last -1 step 1 filebonds 1 autobonds 1 waitfor all"
18

    
19
  REAL(KREAL) :: X,Y,Z
20
  CHARACTER(LCHARS) :: TITLE
21
  LOGICAL :: Debug
22

    
23
  INTERFACE
24
     function valid(string) result (isValid)
25
       CHARACTER(*), intent(in) :: string
26
       logical                  :: isValid
27
     END function VALID
28
  END INTERFACE
29

    
30
  debug=valid('write_vasp')
31
  if (debug) WRITE(*,*) '================ Entering Write_VASP ===================='
32

    
33
  ALLOCATE(GeomTmpC(3*Nat), GeomTmp(NCoord))
34

    
35
  Line2="00"
36
  DO IGeom=1,NGeomF
37
     WRITE(Line,'(I5)') IGeom-1
38
     Idx=2-Len_TRIM(ADJUSTL(Line))
39
     OPEN(IOTMP,File=TRIM(POSCAR) // "_" // Line2(1:Idx) // AdjustL(TRIM(Line)))
40
     ! we convert the coordinates into Cartesian coordinates
41
     SELECT CASE (Coord)
42
     CASE ('CART','HYBRID')
43
        GeomTmpC=Reshape(reshape(XyzGeomF(IGeom,:,:),(/Nat,3/),ORDER=(/2,1/)),(/3*Nat/))
44
     CASE ('ZMAT')
45
        GeomTmp=IntCoordF(IGeom,:)
46
        ! we have to generate the cartesian coordinates from the internal coordinates
47
        CAll Int2Cart(nat,indzmat,geomtmp,GeomTmpC)
48
     CASE ('MIXED')
49
        GeomTmp=IntCoordF(IGeom,:)
50
        CAll Mixed2Cart(nat,indzmat,geomtmp,GeomTmpC)
51
     END SELECT
52

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

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

    
57
     Call PrintGeomVasp(Title,geomTmpC,Latr,FrozAtoms,IoTmp)
58

    
59
     CLOSE(IOTMP)
60
  END DO
61

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

    
65
     Line2="00"
66
     WRITE(IOOUT,'(A)') TRIM(FirstWord) // " new " // TRIM(POSCAR) // "_00" // TRIM(LastWords)
67
     DO IGeom=2,NGeomF
68
        WRITE(Line,'(I5)') IGeom-1
69
        Idx=2-Len_TRIM(ADJUSTL(Line))
70
        WRITE(IOOUT,'(A)') TRIM(FirstWord) // " addfile " // TRIM(POSCAR) //  &
71
             "_" // Line2(1:Idx) // TRIM(ADJUSTL(Line)) // TRIM(LastWords)
72
     END DO
73
     WRITE(IOOUT,*) "## End of List"
74
  END IF
75

    
76
  if (debug) WRITE(*,*) '================  Write_VASP OVER ===================='
77
  DeALLOCATE(GeomTmpC, GeomTmp)
78

    
79
END SUBROUTINE Write_vasp