Statistiques
| Révision :

root / src / Io_module.f90

Historique | Voir | Annoter | Télécharger (5,39 ko)

1
MODULE Io_Module
2
! This module contains all variables related to IO
3

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

    
35
  use VarTypes
36

    
37
  IMPLICIT NONE
38

    
39
  SAVE
40

    
41
  INTEGER(KINT) :: IOIN=11, IOOUT=12, IOCART=14
42
  INTEGER(KINT) :: IOGEOM=15, IODAT=16,IoGplot=17
43
  INTEGER(KINT), PARAMETER :: IOTMP=21,IOTMP2=22, IOTMP3=23
44
  INTEGER(KINT), PARAMETER :: IOERR=0
45
  CHARACTER(SCHARS) :: RunMode
46

    
47
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
48
!
49
! System dependent delimiter for filename
50
! / on Linux; \ on windows, ...
51
  CHARACTER :: FileDelim
52

    
53

    
54
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
55
! 
56
!  Some parameters for unit conversion
57
!
58
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
59

    
60
  REAL(KREAL), PARAMETER :: au2eV=27.21183d0
61
  REAL(KREAL), PARAMETER :: ev2au= 1.d0/au2eV
62
  REAL(KREAL), PARAMETER :: au2kcal=627.509608d0
63
  REAL(KREAL), PARAMETER :: eV2kcal=23.06035d0
64

    
65
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
66
!
67
! Variables for Gaussian input
68
!
69
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
70
  TYPE (Input_line), POINTER :: Gauss_Root, Gauss_End, Gauss_Comment
71
  TYPE (Input_Line), POINTER :: Current, Previous
72

    
73
  CHARACTER(LCHARS) :: Gauss_Charge
74
  CHARACTER(LCHARS), ALLOCATABLE :: Gauss_paste(:)
75

    
76
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
77
!
78
! Variables for MOPAC input
79
!
80
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
81
  TYPE (Input_line), POINTER :: Mopac_Root, Mopac_End, Mopac_Comment
82
  TYPE (Input_Line), POINTER :: CurCom
83
  CHARACTER(LCHARS) :: Mopac_EndGeom
84

    
85
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
86
!
87
! Variables for VASP input/output
88
!
89
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
90
  CHARACTER(LCHARS) :: Vasp_Title, Vasp_Types, Vasp_comment, Vasp_direct
91
  CHARACTER(LCHARS) :: Vasp_Types_User
92
  REAL(KREAL) :: vasp_Param
93
  CHARACTER(4), ALLOCATABLE :: FFF(:,:) !(3,na)
94
  INTEGER(KINT) :: NbTypes
95
  INTEGER(KINT), PARAMETER :: MaxType=100
96
  CHARACTER(2) :: Attypes(MaxType)='  '
97
! VASP5 is true when the POSCAR is in the new POSCAR file
98
  LOGICAL :: VASP5
99
! VASP_SelectD is true if Selective Dynamic is selected
100
  LOGICAL :: VASP_SelectD
101

    
102

    
103
! WriteVasp controls the printing of the images coordinates in POSCAR files.
104
  LOGICAL :: WriteVasp
105

    
106
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
107
!
108
! Variables for SIESTA input
109
!
110
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
111
  TYPE (Input_line), POINTER :: Siesta_Input
112
  TYPE (Input_line), POINTER :: Siesta_Comment_Species,Siesta_Comment_Coord
113
  TYPE (Input_Line), POINTER :: CurComSpec, CurComCoord
114
  CHARACTER(LCHARS) :: Siesta_Label, Siesta_CoordFile
115
! Number of species used in Siesta
116
  INTEGER(KINT) :: Siesta_NbSpecies
117
! Mass number for each species (atomic number)
118
  INTEGER(KINT), ALLOCATABLE :: Siesta_SpeciesMass(:) ! NbSpecies
119
! Name of each species
120
  CHARACTER(LCHARS), ALLOCATABLE :: Siesta_SpeciesName(:) ! NbSpecies
121
! Species for each atom
122
  INTEGER(KINT), ALLOCATABLE :: IdxSpecies(:) ! NAt
123
! What to add at the end of each coordinate line
124
  CHARACTER(LCHARS), ALLOCATABLE :: Siesta_Paste(:) ! Nat
125
! This is the unit (ang or bohr) to read/write the coordinates
126
  REAL(KREAL) :: Siesta_Unit_Read, Siesta_Unit_Write
127
! The lattice constant in case we are in periodic calculation
128
  REAL(KREAL) :: Siesta_LatticeConstant,Siesta_lat_unit
129

    
130
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
131
!
132
! For debug
133
!
134
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
135
  CHARACTER(132) :: DebugFile='Path.valid'
136

    
137
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
138
!
139
! For Printing
140
!
141
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
142
  CHARACTER(LCHARS) :: PathName
143

    
144
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
145
!
146
! For Energy+Gradient calculations
147
!
148
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
149
! CalcName: Prefix for the files used for the energy and gradient calculations
150
  CHARACTER(LCHARS) :: CalcName
151

    
152
! ISuffix: Suffix for the input file
153
  CHARACTER(LCHARS) :: ISuffix
154
! OSuffix: suffix for the output file.
155
  CHARACTER(LCHARS) :: OSuffix
156

    
157
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
158
!
159
! For printing energies
160
!
161
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
162
! Name of the unit used by internally by the 'engine' program
163
  CHARACTER(SCHARS) :: UnitProg="au"
164
! Conversion factor from energy program to kcal/mol
165
  REAL(KREAL) :: ConvE
166

    
167
END MODULE IO_MODULE