root / src / Io_module.f90 @ 6
Historique | Voir | Annoter | Télécharger (2,33 ko)
1 |
MODULE Io_Module |
---|---|
2 |
! This module contains all variables related to IO |
3 |
|
4 |
use VarTypes |
5 |
|
6 |
IMPLICIT NONE |
7 |
|
8 |
SAVE |
9 |
|
10 |
INTEGER(KINT) :: IOIN=11, IOOUT=12, IOCART=14 |
11 |
INTEGER(KINT), PARAMETER :: IOTMP=21,IOTMP2=22, IOTMP3=23 |
12 |
|
13 |
TYPE Input_Line |
14 |
CHARACTER(LCHARS) :: Line |
15 |
TYPE (Input_Line), POINTER :: Next |
16 |
END TYPE Input_Line |
17 |
|
18 |
CHARACTER(SCHARS) :: RunMode |
19 |
|
20 |
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
21 |
! |
22 |
! Some parameters for unit conversion |
23 |
! |
24 |
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
25 |
|
26 |
REAL(KREAL), PARAMETER :: ev2au= 0.036749324445d0 |
27 |
|
28 |
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
29 |
! |
30 |
! Variables for Gaussian input |
31 |
! |
32 |
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
33 |
TYPE (Input_line), POINTER :: Gauss_Root, Gauss_End, Gauss_Comment |
34 |
TYPE (Input_Line), POINTER :: Current, Previous |
35 |
|
36 |
CHARACTER(LCHARS) :: Gauss_Charge |
37 |
CHARACTER(LCHARS), ALLOCATABLE :: Gauss_paste(:) |
38 |
|
39 |
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
40 |
! |
41 |
! Variables for MOPAC input |
42 |
! |
43 |
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
44 |
TYPE (Input_line), POINTER :: Mopac_Root, Mopac_End, Mopac_Comment |
45 |
TYPE (Input_Line), POINTER :: CurCom |
46 |
CHARACTER(LCHARS) :: Mopac_EndGeom |
47 |
|
48 |
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
49 |
! |
50 |
! Variables for VASP input/output |
51 |
! |
52 |
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
53 |
CHARACTER(LCHARS) :: Vasp_Title, Vasp_Types, Vasp_comment, Vasp_direct |
54 |
REAL(KREAL) :: vasp_Param |
55 |
CHARACTER(4), ALLOCATABLE :: FFF(:,:) !(3,na) |
56 |
INTEGER(KINT) :: NbTypes |
57 |
INTEGER(KINT), PARAMETER :: MaxType=100 |
58 |
CHARACTER(2) :: Attypes(MaxType)=' ' |
59 |
! WriteVasp controls the printing of the images coordinates in POSCAR files. |
60 |
LOGICAL :: WriteVasp |
61 |
|
62 |
|
63 |
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
64 |
! |
65 |
! For debug |
66 |
! |
67 |
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
68 |
CHARACTER(132) :: DebugFile='Path.valid' |
69 |
|
70 |
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
71 |
! |
72 |
! For Printing |
73 |
! |
74 |
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
75 |
CHARACTER(LCHARS) :: PathName |
76 |
|
77 |
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
78 |
! |
79 |
! For Energy+Gradient calculations |
80 |
! |
81 |
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
82 |
! CalcName: Prefix for the files used for the energy and gradient calculations |
83 |
CHARACTER(LCHARS) :: CalcName |
84 |
|
85 |
! ISuffix: Suffix for the input file |
86 |
CHARACTER(LCHARS) :: ISuffix |
87 |
! OSuffix: suffix for the output file. |
88 |
CHARACTER(LCHARS) :: OSuffix |
89 |
|
90 |
|
91 |
END MODULE IO_MODULE |