1  !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2! Copyright 2010.  Los Alamos National Security, LLC. This material was    !
3! produced under U.S. Government contract DE-AC52-06NA25396 for Los Alamos !
4! National Laboratory (LANL), which is operated by Los Alamos National     !
5! Security, LLC for the U.S. Department of Energy. The U.S. Government has !
6! rights to use, reproduce, and distribute this software.  NEITHER THE     !
7! GOVERNMENT NOR LOS ALAMOS NATIONAL SECURITY, LLC MAKES ANY WARRANTY,     !
8! EXPRESS OR IMPLIED, OR ASSUMES ANY LIABILITY FOR THE USE OF THIS         !
9! SOFTWARE.  If software is modified to produce derivative works, such     !
10! modified software should be clearly marked, so as not to confuse it      !
11! with the version available from LANL.                                    !
12!                                                                          !
13! Additionally, this program is free software; you can redistribute it     !
14! and/or modify it under the terms of the GNU General Public License as    !
15! published by the Free Software Foundation; version 2.0 of the License.   !
16! Accordingly, this program is distributed in the hope that it will be     !
17! useful, but WITHOUT ANY WARRANTY; without even the implied warranty of   !
18! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General !
19! Public License for more details.                                         !
20!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
21
22SUBROUTINE READCONTROLS
23
24  USE CONSTANTS_MOD
25  USE SETUPARRAY
26  USE PPOTARRAY
27  USE NEBLISTARRAY
28  USE COULOMBARRAY
29  USE FERMICOMMON
30  USE SPARSEARRAY
31  USE RELAXCOMMON
32
33  IMPLICIT NONE
34
35  CHARACTER(LEN=20) :: HD
36
37  IF (EXISTERROR) RETURN
38
39  OPEN(UNIT=13, STATUS="OLD", FILE=TRIM(PARAMPATH)//"/control.in")
40
41  !
42  ! CONTROL determines how the density matrix is going to be
43  ! calculated: 1 = diagonalization, 2 = SP2 purification,
44  ! 3 = recursive expansion of the Fermi operator, 4 = SP2T,
45  ! 5 = SP2 Fermi (truncated SP2)
46  !
47
48  READ(13,*) HD, CONTROL
49
50  !
51  ! BASISTYPE can equal "ORTHO" OR "NONORTHO",
52  !
53
54  READ(13,*) HD, BASISTYPE
55
56  IF (BASISTYPE .NE. "ORTHO" .AND. BASISTYPE .NE. "NONORTHO") THEN
57     CALL ERRORS("readcontrols","Error defining basis type (ortho/nonortho)")
58  ENDIF
59
60  READ(13,*) HD, SCLTYPE ! Choose whether to use the analytic forms or tables
61
62  READ(13,*) HD, DEBUGON
63
64
65  !
66  ! Read the order of the recursion in the expansion of the Fermi
67  ! operator, M.
68  !
69
70  READ(13,*) HD, FERMIM
71
72  ! If we're using the expansion of the Fermi operator, we can
73  ! use a LAPACK routine or Niklasson's conjugate gradient method to
74  ! solve AX = B. CGORLIB: 0 = LAPACK, 1 = conjugate gradient
75  ! CGTOL = the user-supplied tolerance for the CG solution of AX = B
76
77  READ(13,*) HD, CGORLIB, HD, CGTOL
78
79  CGTOL2 = CGTOL*CGTOL
80
81  ! Electronic temperature, in eV
82
83  READ(13,*) HD, KBT
84
85  !
86  ! Read the number of recursions for the truncated, finite
87  ! temperature SP2 algorithm
88  !
89
90  READ(13,*) HD, NORECS
91
92  !
93  ! What kind of entropy are we going to use in a finite Te calculation
94  !
95  ! ENTROPYKIND = 0 : none
96  ! ENTROPYKIND = 1 : exact for Fermi-Dirac occupation
97  ! ENTROPYKIND = 2 : Different form of exact expression that may be useful
98  ! when using CONTROL = 5
99  ! ENTROPYKIND = 3 : 4th order expansion of exact form (no diag)
100  ! ENTROPYKIND = 4 : 8th order expansion of exact form (no diag)
101  !
102
103  READ(13,*) HD, ENTROPYKIND
104
105  !
106  ! Do we want long-range C/R^6 tails?
107  !
108  ! PPOTON = 1: Turn on pairwise interaction
109  ! PPOTON = 0: Turn it off (useful for fitting)
110  !
111  ! VDWON = 0: No C/R^6 tails
112  ! VDWON = 1: Use tails
113  !
114
115  READ(13,*) HD, PPOTON, HD, PLUSDON
116
117
118  !
119  ! Are we doing a spin-polarized calculation?
120  ! SPINON = 1 = yes
121  ! SPINON = 0 = no
122
123  READ(13,*) HD, SPINON, HD, SPINTOL
124
125  !
126  ! Controls for electrostatics:
127  !
128  ! ELECTRO: 0 = LCN is applied, 1 = charge dependent TB on
129  ! ELECMETH: 0 = Ewald  summation, 1 = All real space
130  ! ELEC_ETOL: Tolerance on energy when determining charges (not implemented)
131  ! ELEC_QTOL: Tolerance on charges during self-consistent calc
132  !
133
134  READ(13,*) HD, ELECTRO, HD, ELECMETH, HD, ELEC_ETOL, HD, ELEC_QTOL
135
136  !
137  ! COULACC: Accuracy for the Ewald method (1.0e-4 works)
138  ! COULCUT: If we're using the Ewald method, this is the cut-off for the
139  ! real space part. If we're doing it all in real space, this is the radial
140  ! cut-off for the sum.
141  ! COULR1: If we're doing it in real space, the cut-off tail on 1/R is
142  ! applied here at terminated at COULCUT.
143  !
144
145  READ(13,*) HD, COULACC, HD, COULCUT, HD, COULR1
146
147  !
148  ! MAXSCF:  Maximum number of SCF cycles
149  !
150
151  READ(13,*) HD, MAXSCF
152
153  !
154  ! BREAKTOL: Tolerance for breaking SP2 loops
155  ! MINSP2ITER: Minimum number of iterations during SP2 purification
156  !
157
158  READ(13,*) HD, BREAKTOL, HD, MINSP2ITER, HD, SP2CONV
159
160  !
161  ! FULLQCONV: 0 = We'll run QITER SCF cycles during MD, = 1, we'll run
162  ! SCF cycles until we've reached ELEC_QTOL. Only important for MD
163  ! QITER: Number of SCF cycles we're going to run at each MD time step
164  !
165
166  READ(13,*) HD, FULLQCONV, HD, QITER
167
168  !
169  ! QMIX AND SPINMIX are the coefficients for the linear mixing of
170  ! new and old charge and spin densities, respectively, during SCF cycles
171  !
172
173  READ(13,*) HD, QMIX, HD, SPINMIX, HD, MDMIX
174
175  !
176  ! ORDERNMOL: Turn on molecule-ID-based density matrix blocking
177  !
178
179  READ(13,*) HD, ORDERNMOL
180
181  !
182  ! SPARSEON: 0 = all dense matrix stuff, 1 = use CSR format and
183  ! Gustavson's algorithm for matrix-matrix multiplication
184  ! THRESHOLDON: 0 = do not throw away elements; 1 = throw away elements
185  ! NUMTHRESH: If THRESHOLDON = 1 throw away element whose absolute value is
186  ! smaller than NUMTHRESH
187  ! FILLINSTOP: Number of purification cycles beyond which we stop allowing
188  ! for further fill-in
189  !
190
191  READ(13,*) HD, SPARSEON, HD, THRESHOLDON,  HD, NUMTHRESH, HD, FILLINSTOP, HD, BLKSZ
192
193  !
194  ! MSPARSE: value for M when SPARSEON = 1, used by sp2 sparse algorithm
195  !          0 = value for M is not known, defaults to N
196  !
197
198  READ(13,*) HD, MSPARSE
199
200  !
201  ! LCNON: 0 = during charge neutral MD simulations we'll run LCNITER SCF
202  ! cycles at each time step, 1 = we'll run SCF cycles until CHTOL is reached
203  ! LCNITER: Number of SCF cycles to achieve LCN at each MD time step
204  ! CHTOL: Tolerance on atomic charges (Mulliken) before LCN is declared
205  !
206
207  READ(13,*) HD, LCNON, HD, LCNITER, HD, CHTOL
208
209  !
210  ! Read the SKIN for the neighbor list (Angstrom)
211  !
212
213  READ(13,*) HD, SKIN
214
215  !
216  ! RELAXME: 0 = Don't run relaxation, 1 = relax geometry
217  ! RELTYPE: SD = steepest descent, CG = conjugate gradient
218  ! MXRLX: Maximum number of steps in the geometry optimization
219  ! RLXFTOT: Run optimization until all forces are less than RLXFTOL
220  !
221
222  READ(13,*) HD, RELAXME, HD, RELTYPE, HD, MXRLX, HD, RLXFTOL
223
224  !
225  ! MDON: 0 = Molecular dynamics off, 1 = Molecular dynamics on
226  ! (MD is controlled using the file MDcontroller)
227  !
228
229  READ(13,*) HD, MDON
230
231  !
232  ! PBCON: 1 = full periodic boundary conditions, 0 = gas phase: no pbc and
233  ! electrostatics done all in real space
234  !
235
236  READ(13,*) HD, PBCON
237
238  READ(13,*) HD, RESTART
239
240  ! Add or remove electrons. 2+ -> charge = +2 since TOTNE = TOTNE - CHARGE
241
242  READ(13,*) HD, CHARGE
243
244  !
245  ! XBOON: 0 = Niklasson's extended Lagrangian Born-Oppenheimer MD off,
246  ! 1 = on.
247  !
248
249  READ(13,*) HD, XBOON
250
251  !
252  ! XBODISON: We have the option of turning on damping for the XBO
253  ! to remedy the accumulation of noise. 0 = off, 1 = on.
254  !
255
256  READ(13,*) HD, XBODISON
257
258  !
259  ! XBODISORDER: = Order of the damping function (1 - 9)
260  !
261
262  READ(13,*) HD, XBODISORDER
263
264  FITON = 0
265
266  !
267  ! Read in the number of GPUs per node
268  !
269
270  READ(13,*) HD, NGPU
271
272  ! Are we doing k-space?
273
274  READ(13,*) HD, KON
275
276  ! Do we want to calculate forces too (not always necessary when fitting)
277
278  READ(13,*) HD, COMPFORCE
279
280  ! Turn on the simulated annealing subroutine to fit DOS
281
282
283  READ(13,*) HD, DOSFITON, HD, INT2FIT, HD, MCBETA, HD, NFITSTEP, HD, QFIT, &
284       HD, MCSIGMA
285
286  READ(13,*) HD, PPFITON
287
288  READ(13,*) HD, ALLFITON
289
290  READ(13,*) HD, PPNFITSTEP, HD, BINFITSTEP, HD, PP2FIT, HD, BINT2FIT
291
292  READ(13,*) HD, PPBETA, HD, PPSIGMA, HD, PPNMOL, HD, PPNGEOM
293
294  READ(13,*) HD, PARREP
295
296  ! Dielectric constant
297
298  READ(13,*) HD, RELPERM
299
300  CLOSE(13)
301
302  !
303  ! Summarize the calculation we're doing here
304  !
305
306  !  OPEN(UNIT=99, STATUS="UNKNOWN", FILE="my_last_LATTE_calc")
307
308  !  IF (CONTROL .EQ. 1) THEN
309  !     WRITE(99,*) "Diagonization used to calculate bond order"
310  !  ELSEIF (CONTROL .EQ. 2 .AND. SPARSEON .EQ. 0) THEN
311  !     WRITE(99,*) "Dense matrix SP2 used to calculate bond order"
312  !  ELSEIF (CONTROL .EQ. 2 .AND. SPARSEON .EQ. 1) THEN
313  !     WRITE(99,*) "Quasi-sparse matrix SP2 used to calculated bond order"
314  !  ELSEIF (CONTROL .EQ. 3) THEN
315  !     WRITE(99,*) "Recursive expansion of the Fermi operator"
316  !     IF (CGORLIB .EQ. 0) THEN
317  !        WRITE(99,*) "Dense matrix: using LAPACK routine to solve AX=B"
318  !     ENDIF
319  !     IF (CGORLIB .EQ. 1 .AND. SPARSEON .EQ. 0) THEN
320  !        WRITE(99,*) "Dense matrix conjugate gradient scheme to solve AX=B"
321  !     ELSEIF (CGORLIB .EQ. 1 .AND. SPARSEON .EQ. 1) THEN
322  !        WRITE(99,*) "Sparse matrix conjugate gradient scheme to solve AX=B"
323  !     ENDIF
324  !  ENDIF
325
326  RETURN
327
328END SUBROUTINE READCONTROLS
329