Statistiques
| Révision :

root / src / Io_module.f90 @ 10

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

1 1 pfleura2
MODULE Io_Module
2 1 pfleura2
! This module contains all variables related to IO
3 1 pfleura2
4 1 pfleura2
  use VarTypes
5 1 pfleura2
6 1 pfleura2
  IMPLICIT NONE
7 1 pfleura2
8 1 pfleura2
  SAVE
9 1 pfleura2
10 1 pfleura2
  INTEGER(KINT) :: IOIN=11, IOOUT=12, IOCART=14
11 8 pfleura2
  INTEGER(KINT) :: IOGEOM=15, IODAT=16,IoGplot=17
12 1 pfleura2
  INTEGER(KINT), PARAMETER :: IOTMP=21,IOTMP2=22, IOTMP3=23
13 10 pfleura2
  INTEGER(KINT), PARAMETER :: IOERR=0
14 1 pfleura2
  CHARACTER(SCHARS) :: RunMode
15 1 pfleura2
16 1 pfleura2
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
17 1 pfleura2
!
18 1 pfleura2
!  Some parameters for unit conversion
19 1 pfleura2
!
20 1 pfleura2
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
21 1 pfleura2
22 8 pfleura2
  REAL(KREAL), PARAMETER :: au2eV=27.21183d0
23 8 pfleura2
  REAL(KREAL), PARAMETER :: ev2au= 1.d0/au2eV
24 8 pfleura2
  REAL(KREAL), PARAMETER :: au2kcal=627.509608d0
25 8 pfleura2
  REAL(KREAL), PARAMETER :: eV2kcal=23.06035d0
26 1 pfleura2
27 1 pfleura2
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
28 1 pfleura2
!
29 1 pfleura2
! Variables for Gaussian input
30 1 pfleura2
!
31 1 pfleura2
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
32 1 pfleura2
  TYPE (Input_line), POINTER :: Gauss_Root, Gauss_End, Gauss_Comment
33 1 pfleura2
  TYPE (Input_Line), POINTER :: Current, Previous
34 1 pfleura2
35 1 pfleura2
  CHARACTER(LCHARS) :: Gauss_Charge
36 1 pfleura2
  CHARACTER(LCHARS), ALLOCATABLE :: Gauss_paste(:)
37 1 pfleura2
38 1 pfleura2
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
39 1 pfleura2
!
40 1 pfleura2
! Variables for MOPAC input
41 1 pfleura2
!
42 1 pfleura2
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
43 1 pfleura2
  TYPE (Input_line), POINTER :: Mopac_Root, Mopac_End, Mopac_Comment
44 1 pfleura2
  TYPE (Input_Line), POINTER :: CurCom
45 1 pfleura2
  CHARACTER(LCHARS) :: Mopac_EndGeom
46 1 pfleura2
47 1 pfleura2
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
48 1 pfleura2
!
49 1 pfleura2
! Variables for VASP input/output
50 1 pfleura2
!
51 1 pfleura2
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
52 1 pfleura2
  CHARACTER(LCHARS) :: Vasp_Title, Vasp_Types, Vasp_comment, Vasp_direct
53 1 pfleura2
  REAL(KREAL) :: vasp_Param
54 1 pfleura2
  CHARACTER(4), ALLOCATABLE :: FFF(:,:) !(3,na)
55 1 pfleura2
  INTEGER(KINT) :: NbTypes
56 1 pfleura2
  INTEGER(KINT), PARAMETER :: MaxType=100
57 1 pfleura2
  CHARACTER(2) :: Attypes(MaxType)='  '
58 1 pfleura2
! WriteVasp controls the printing of the images coordinates in POSCAR files.
59 1 pfleura2
  LOGICAL :: WriteVasp
60 1 pfleura2
61 5 pfleura2
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
62 5 pfleura2
!
63 5 pfleura2
! Variables for SIESTA input
64 5 pfleura2
!
65 5 pfleura2
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
66 5 pfleura2
  TYPE (Input_line), POINTER :: Siesta_Input
67 5 pfleura2
  TYPE (Input_line), POINTER :: Siesta_Comment_Species,Siesta_Comment_Coord
68 5 pfleura2
  TYPE (Input_Line), POINTER :: CurComSpec, CurComCoord
69 5 pfleura2
  CHARACTER(LCHARS) :: Siesta_Label, Siesta_CoordFile
70 5 pfleura2
! Number of species used in Siesta
71 5 pfleura2
  INTEGER(KINT) :: Siesta_NbSpecies
72 9 pfleura2
! Mass number for each species (atomic number)
73 9 pfleura2
  INTEGER(KINT), ALLOCATABLE :: Siesta_SpeciesMass(:) ! NbSpecies
74 5 pfleura2
! Name of each species
75 5 pfleura2
  CHARACTER(LCHARS), ALLOCATABLE :: Siesta_SpeciesName(:) ! NbSpecies
76 5 pfleura2
! Species for each atom
77 5 pfleura2
  INTEGER(KINT), ALLOCATABLE :: IdxSpecies(:) ! NAt
78 5 pfleura2
! What to add at the end of each coordinate line
79 5 pfleura2
  CHARACTER(LCHARS), ALLOCATABLE :: Siesta_Paste(:) ! Nat
80 5 pfleura2
! This is the unit (ang or bohr) to read/write the coordinates
81 5 pfleura2
  REAL(KREAL) :: Siesta_Unit_Read, Siesta_Unit_Write
82 5 pfleura2
! The lattice constant in case we are in periodic calculation
83 5 pfleura2
  REAL(KREAL) :: Siesta_LatticeConstant,Siesta_lat_unit
84 1 pfleura2
85 1 pfleura2
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
86 1 pfleura2
!
87 1 pfleura2
! For debug
88 1 pfleura2
!
89 1 pfleura2
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
90 1 pfleura2
  CHARACTER(132) :: DebugFile='Path.valid'
91 1 pfleura2
92 1 pfleura2
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
93 1 pfleura2
!
94 1 pfleura2
! For Printing
95 1 pfleura2
!
96 1 pfleura2
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
97 1 pfleura2
  CHARACTER(LCHARS) :: PathName
98 1 pfleura2
99 1 pfleura2
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
100 1 pfleura2
!
101 1 pfleura2
! For Energy+Gradient calculations
102 1 pfleura2
!
103 1 pfleura2
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
104 1 pfleura2
! CalcName: Prefix for the files used for the energy and gradient calculations
105 1 pfleura2
  CHARACTER(LCHARS) :: CalcName
106 1 pfleura2
107 1 pfleura2
! ISuffix: Suffix for the input file
108 1 pfleura2
  CHARACTER(LCHARS) :: ISuffix
109 1 pfleura2
! OSuffix: suffix for the output file.
110 1 pfleura2
  CHARACTER(LCHARS) :: OSuffix
111 1 pfleura2
112 8 pfleura2
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
113 8 pfleura2
!
114 8 pfleura2
! For printing energies
115 8 pfleura2
!
116 8 pfleura2
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
117 8 pfleura2
! Name of the unit used by internally by the 'engine' program
118 8 pfleura2
  CHARACTER(SCHARS) :: UnitProg="au"
119 8 pfleura2
! Conversion factor from energy program to kcal/mol
120 8 pfleura2
  REAL(KREAL) :: ConvE
121 1 pfleura2
122 1 pfleura2
END MODULE IO_MODULE