-
Notifications
You must be signed in to change notification settings - Fork 22
/
Copy pathrestart.f90
287 lines (262 loc) · 10.4 KB
/
restart.f90
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
!
! Copyright (C) 2002-2005 Quantum ESPRESSO group
! This file is distributed under the terms of the
! GNU General Public License. See the file `License'
! in the root directory of the present distribution,
! or http://www.gnu.org/copyleft/gpl.txt .
!
! written by Carlo Cavazzoni
!-----------------------------------------------------------------------
SUBROUTINE writefile_x &
& ( h,hold,nfi,c0,cm,taus,tausm,vels,velsm,acc, &
& lambda,lambdam,descla,xnhe0,xnhem,vnhe,xnhp0,xnhpm,vnhp,nhpcl,nhpdim,ekincm,&
& xnhh0,xnhhm,vnhh,velh, fion, tps, mat_z, occ_f, rho )
!-----------------------------------------------------------------------
!
USE kinds, ONLY: DP
USE ions_base, ONLY: nsp, na, cdmi, taui
USE cell_base, ONLY: s_to_r
USE cp_restart, ONLY: cp_writefile
USE cp_interfaces, ONLY: set_evtot, set_eitot, c_bgrp_expand, c_bgrp_pack
USE electrons_base, ONLY: nspin, nbnd, nbsp, iupdwn, nupdwn, nbspx
USE electrons_module, ONLY: ei
USE io_files, ONLY: tmp_dir
USE ensemble_dft, ONLY: tens
USE mp, ONLY: mp_bcast
USE control_flags, ONLY: tksw, ndw, io_level, twfcollect
USE electrons_module, ONLY: collect_c
USE descriptors, ONLY: la_descriptor
USE gvecw, ONLY: ngw
USE wannier_module, ONLY : wfc ! BS
!
implicit none
integer, INTENT(IN) :: nfi
REAL(DP), INTENT(IN) :: h(3,3), hold(3,3)
complex(DP), INTENT(IN) :: c0(:,:), cm(:,:)
REAL(DP), INTENT(IN) :: tausm(:,:), taus(:,:), fion(:,:)
REAL(DP), INTENT(IN) :: vels(:,:), velsm(:,:)
REAL(DP), INTENT(IN) :: acc(:), lambda(:,:,:), lambdam(:,:,:)
REAL(DP), INTENT(IN) :: xnhe0, xnhem, vnhe, ekincm
REAL(DP), INTENT(IN) :: xnhp0(:), xnhpm(:), vnhp(:)
integer, INTENT(in) :: nhpcl, nhpdim
REAL(DP), INTENT(IN) :: xnhh0(3,3),xnhhm(3,3),vnhh(3,3),velh(3,3)
REAL(DP), INTENT(in) :: tps
REAL(DP), INTENT(in) :: rho(:,:)
REAL(DP), INTENT(in) :: occ_f(:)
REAL(DP), INTENT(in) :: mat_z(:,:,:)
TYPE(la_descriptor), INTENT(IN) :: descla(:)
REAL(DP) :: ht(3,3), htm(3,3), htvel(3,3), gvel(3,3)
INTEGER :: nk = 1, ispin, i, ib
REAL(DP) :: xk(3,1) = 0.0d0, wk(1) = 2.0d0
COMPLEX(DP), ALLOCATABLE :: ctot(:,:)
REAL(DP), ALLOCATABLE :: eitot(:,:)
INTEGER :: nupdwn_tot( 2 ), iupdwn_tot( 2 )
if ( ndw < 1 ) then
!
! Do not write restart file if the unit number
! is negative, this is used mainly for benchmarks and tests
!
return
!
end if
CALL c_bgrp_expand( c0 )
CALL c_bgrp_expand( cm )
ht = TRANSPOSE( h )
htm = TRANSPOSE( hold )
htvel = TRANSPOSE( velh )
gvel = 0.0d0
nupdwn_tot = nupdwn
iupdwn_tot(1) = iupdwn(1)
iupdwn_tot(2) = nupdwn(1) + 1
!
ALLOCATE( eitot( nupdwn_tot(1), nspin ) )
!
CALL set_eitot( eitot )
!
IF( tksw ) THEN
!
ALLOCATE( ctot( SIZE( c0, 1 ), nupdwn_tot(1) * nspin ) )
!
CALL set_evtot( c0, ctot, lambda, descla, iupdwn_tot, nupdwn_tot )
!
END IF
!
IF( tens ) THEN
!
CALL cp_writefile( ndw, .TRUE., nfi, tps, acc, nk, xk, wk, &
ht, htm, htvel, gvel, xnhh0, xnhhm, vnhh, taui, cdmi , taus, &
vels, tausm, velsm, fion, vnhp, xnhp0, xnhpm, nhpcl,nhpdim, occ_f , &
occ_f , lambda, lambdam, xnhe0, xnhem, vnhe, ekincm, ei, &
rho, c0, cm, ctot, iupdwn, nupdwn, iupdwn, nupdwn, wfc, mat_z = mat_z ) ! BS added wfc
!
ELSE
!
CALL cp_writefile( ndw, .TRUE., nfi, tps, acc, nk, xk, wk, &
ht, htm, htvel, gvel, xnhh0, xnhhm, vnhh, taui, cdmi , taus, &
vels, tausm, velsm, fion, vnhp, xnhp0, xnhpm, nhpcl,nhpdim, occ_f,&
occ_f , lambda, lambdam, xnhe0, xnhem, vnhe, ekincm, eitot, &
rho, c0, cm, ctot, iupdwn, nupdwn, iupdwn_tot, nupdwn_tot, wfc ) ! BS added wfc
!
END IF
DEALLOCATE( eitot )
!
IF( tksw ) DEALLOCATE( ctot )
!
CALL c_bgrp_pack( c0 )
CALL c_bgrp_pack( cm )
return
end subroutine writefile_x
!-----------------------------------------------------------------------
subroutine readfile_x &
& ( flag, h,hold,nfi,c0,cm,taus,tausm,vels,velsm,acc, &
& lambda,lambdam,xnhe0,xnhem,vnhe,xnhp0,xnhpm,vnhp,nhpcl,nhpdim,ekincm,&
& xnhh0,xnhhm,vnhh,velh,&
& fion, tps, mat_z, occ_f )
!-----------------------------------------------------------------------
!
! read from file and distribute data calculated in preceding iterations
!
USE kinds, ONLY : DP
USE io_files, ONLY : tmp_dir
USE electrons_base, ONLY : nbnd, nbsp, nspin, nupdwn, iupdwn, keep_occ, nbspx
USE gvecw, ONLY : ngw
USE ions_base, ONLY : nsp, na, cdmi, taui
USE cp_restart, ONLY : cp_readfile, cp_read_cell, cp_read_wfc
USE ensemble_dft, ONLY : tens
USE autopilot, ONLY : event_step, event_index, max_event_step
USE cp_autopilot, ONLY : employ_rules
USE control_flags, ONLY : ndr
USE cp_interfaces, ONLY : c_bgrp_pack
USE wannier_module, ONLY : wfc ! BS
!
implicit none
INTEGER, INTENT(in) :: flag
integer :: nfi
REAL(DP) :: h(3,3), hold(3,3)
complex(DP) :: c0(:,:), cm(:,:)
REAL(DP) :: tausm(:,:),taus(:,:), fion(:,:)
REAL(DP) :: vels(:,:), velsm(:,:)
REAL(DP) :: acc(:),lambda(:,:,:), lambdam(:,:,:)
REAL(DP) :: xnhe0,xnhem,vnhe
REAL(DP) :: xnhp0(:), xnhpm(:), vnhp(:)
integer, INTENT(inout) :: nhpcl,nhpdim
REAL(DP) :: ekincm
REAL(DP) :: xnhh0(3,3),xnhhm(3,3),vnhh(3,3),velh(3,3)
REAL(DP), INTENT(OUT) :: tps
REAL(DP), INTENT(INOUT) :: mat_z(:,:,:), occ_f(:)
!
REAL(DP) :: ht(3,3), htm(3,3), htvel(3,3), gvel(3,3)
integer :: nk = 1, ispin, i, ib
REAL(DP) :: xk(3,1) = 0.0d0, wk(1) = 2.0d0
REAL(DP), ALLOCATABLE :: occ_ ( : )
REAL(DP) :: b1(3) , b2(3), b3(3)
IF( flag == -1 ) THEN
CALL cp_read_cell( ndr, tmp_dir, .TRUE., ht, htm, htvel, gvel, xnhh0, xnhhm, vnhh )
h = TRANSPOSE( ht )
hold = TRANSPOSE( htm )
velh = TRANSPOSE( htvel )
RETURN
END IF
IF ( flag == 0 ) THEN
DO ispin = 1, nspin
CALL cp_read_wfc( ndr, tmp_dir, 1, 1, ispin, nspin, c2 = cm(:,:), tag = 'm' )
END DO
CALL c_bgrp_pack( cm )
RETURN
END IF
ALLOCATE( occ_ ( SIZE( occ_f ) ) )
IF( tens ) THEN
CALL cp_readfile( ndr, .TRUE., nfi, tps, acc, nk, xk, wk, &
ht, htm, htvel, gvel, xnhh0, xnhhm, vnhh, taui, cdmi, taus, &
vels, tausm, velsm, fion, vnhp, xnhp0, xnhpm, nhpcl,nhpdim,occ_ , &
occ_ , lambda, lambdam, b1, b2, b3, &
xnhe0, xnhem, vnhe, ekincm, c0, cm, wfc, mat_z = mat_z ) ! BS added wfc
ELSE
CALL cp_readfile( ndr, .TRUE., nfi, tps, acc, nk, xk, wk, &
ht, htm, htvel, gvel, xnhh0, xnhhm, vnhh, taui, cdmi, taus, &
vels, tausm, velsm, fion, vnhp, xnhp0, xnhpm, nhpcl,nhpdim,occ_ , &
occ_ , lambda, lambdam, b1, b2, b3, &
xnhe0, xnhem, vnhe, ekincm, c0, cm, wfc ) ! BS added wfc
END IF
!
! AutoPilot (Dynamic Rules) Implementation
event_index = 1
do while (event_step(event_index) <= nfi)
! Assuming that the remaining dynamic parm values are set correctly by reading
! the the restart file.
! if this is not true, employ rules as events are updated right here as:
call employ_rules()
event_index = event_index + 1
if( event_index > max_event_step ) then
CALL errore( ' readfile ' , ' maximum events exceeded for dynamic rules ' , 1 )
end if
enddo
IF( .NOT. keep_occ ) THEN
occ_f( : ) = occ_ ( : )
END IF
CALL c_bgrp_pack( cm )
CALL c_bgrp_pack( c0 )
!
DEALLOCATE( occ_ )
return
end subroutine readfile_x
!------------------------------------------------------------------------------!
SUBROUTINE set_eitot_x( eitot )
!------------------------------------------------------------------------------!
USE kinds, ONLY: DP
USE electrons_base, ONLY: nupdwn, nspin
USE electrons_module, ONLY: ei
!
IMPLICIT NONE
!
REAL(DP), INTENT(OUT) :: eitot(:,:)
!
INTEGER :: n
!
eitot = 0.0d0
!
eitot( 1:nupdwn(1), 1 ) = ei( 1:nupdwn(1), 1 )
IF( nspin == 2 ) eitot( 1:nupdwn(2), 2 ) = ei( 1:nupdwn(2), 2 )
!
RETURN
END SUBROUTINE set_eitot_x
!------------------------------------------------------------------------------!
SUBROUTINE set_evtot_x( c0, ctot, lambda, descla, iupdwn_tot, nupdwn_tot )
!------------------------------------------------------------------------------!
USE kinds, ONLY: DP
USE electrons_base, ONLY: nupdwn, nspin, iupdwn, nudx
USE electrons_module, ONLY: ei
USE cp_interfaces, ONLY: crot, collect_lambda
USE descriptors, ONLY: la_descriptor
!
IMPLICIT NONE
!
COMPLEX(DP), INTENT(IN) :: c0(:,:)
COMPLEX(DP), INTENT(OUT) :: ctot(:,:)
REAL(DP), INTENT(IN) :: lambda(:,:,:)
INTEGER, INTENT(IN) :: iupdwn_tot(2), nupdwn_tot(2)
TYPE(la_descriptor), INTENT(IN) :: descla(:)
!
REAL(DP), ALLOCATABLE :: eitmp(:)
REAL(DP), ALLOCATABLE :: lambda_repl(:,:)
!
ALLOCATE( eitmp( nudx ) )
ALLOCATE( lambda_repl( nudx, nudx ) )
!
ctot = 0.0d0
!
CALL collect_lambda( lambda_repl, lambda(:,:,1), descla(1) )
!
CALL crot( ctot, c0, SIZE( c0, 1 ), nupdwn(1), iupdwn_tot(1), iupdwn(1), lambda_repl, nudx, eitmp )
!
IF( nspin == 2 ) THEN
CALL collect_lambda( lambda_repl, lambda(:,:,2), descla(2) )
CALL crot( ctot, c0, SIZE( c0, 1 ), nupdwn(2), iupdwn_tot(2), iupdwn(2), lambda_repl, nudx, eitmp )
END IF
!
DEALLOCATE( lambda_repl )
!
DEALLOCATE( eitmp )
!
RETURN
END SUBROUTINE set_evtot_x