44 FUNCTION siesta_run_construct(run_comm, verbose)
45 USE nscalingtools,
ONLY: myenvvariables, parsolver, siesta_comm
46 USE descriptor_mod,
ONLY: lscalapack, inhessian, iam, nprocs, &
47 nprow, npcol, icontxt, icontxt_1xp, &
48 icontxt_px1, icontxt_global, isroot, &
51 USE prof_mod,
ONLY: profinit
54 USE perturbation,
ONLY: init_data
55 USE hessian,
ONLY: hesspass
58 USE diagnostics_mod,
ONLY: toroidal_flux0
66 TYPE (siesta_run_class),
POINTER :: siesta_run_construct
67 INTEGER,
INTENT(in) :: run_comm
68 LOGICAL,
INTENT(in) :: verbose
75 ALLOCATE(siesta_run_construct)
77 CALL siesta_error_clear_all
83 siesta_comm = run_comm
95 CALL getranks(iam, nprocs)
103 CALL blacs_pinfo(iam, nprocs)
104 CALL blacs_setup(iam, nprocs)
105 DO nprow = int(sqrt(dble(nprocs))) + 1, 1, -1
106 npcol = int( nprocs/nprow )
107 IF (nprow*npcol .eq. nprocs)
EXIT
110 CALL blacs_get(0, 0, icontxt)
111 CALL blacs_gridinit(icontxt,
'C', nprow, npcol)
113 CALL blacs_get(0, 0, icontxt_1xp)
114 CALL blacs_gridinit(icontxt_1xp,
'R', 1, nprow*npcol)
116 CALL blacs_get(0, 0, icontxt_px1)
117 CALL blacs_gridinit(icontxt_px1,
'C', nprow*npcol, 1)
119 icontxt_global = icontxt_1xp
121 CALL blacs_gridinfo(icontxt, nprow, npcol, myrow, mycol)
122 isroot = (myrow .eq. 0) .and. (mycol .eq. 0)
124 WRITE (*,1000) nprow, npcol
125 WRITE (*,1001) icontxt_global, icontxt, icontxt_1xp, icontxt_px1
135 siesta_run_construct%time_on = ton
142 init_data_time = toff - ton
144 1000
FORMAT(
'nprow,npcol ',2(x,i5))
145 1001
FORMAT(
'icontxt_global,icontxt,icontxt_1xp,icontxt_px1 ',4(x,i5))
147 END FUNCTION siesta_run_construct
162 SUBROUTINE siesta_run_destruct(this, finalize_mpi, close_wout)
163 USE nscalingtools,
ONLY: output_timings, gettimes, parsolver, &
164 parfunctisl, pargmres, sksdbg, tofu, &
167 USE descriptor_mod,
ONLY: iam, icontxt, lscalapack, myrow, mycol, nprocs
171 USE hessian,
ONLY: levmarq_param, mupar, asym_index, dealloc_hessian
172 USE quantities,
ONLY: fbdy, dealloc_quantities
173 USE dumping_mod,
ONLY: write_output
174 USE diagnostics_mod,
ONLY: write_profiles, dealloc_diagnostics
179 USE prof_mod,
ONLY: profstat
184 TYPE (siesta_run_class),
POINTER :: this
185 LOGICAL,
INTENT(in) :: finalize_mpi
186 LOGICAL,
INTENT(in) :: close_wout
195 time_total = toff - this%time_on
197 IF (output_timings)
THEN
202 DO i = 6, unit_out, unit_out-6
203 IF (.NOT.
lverbose .AND. i.EQ.6) cycle
204 WRITE (i, 1000)
nprecon, levmarq_param, mupar, asym_index
205 WRITE (i,
'(a,i5)')
' Number processors: ', nprocs
207 WRITE (i, 1002) time_total, fbdy(1),
209 time_diag_prec, fbdy(3),
210 time_block_prec, fbdy(4),
211 time_factor_blocks, fbdy(5),
212 time_toijsp, fbdy(6),
216 time_update_pres, fbdy(7),
217 time_update_bfield, fbdy(8),
218 time_current, fbdy(9),
219 get_force_harmonics_time, fbdy(10),
220 time_update_force, fbdy(11),
221 time_update_upperv, fbdy(12),
222 time_update_state, fbdy(13),
225 (diag_add_pert_time + block_add_pert_time),
229 WRITE (i,*)
'PARSOLVER=T : NSCALED'
230 ELSE IF (lscalapack)
THEN
231 WRITE (i,*)
'PARSOLVER=F : SCALAPACK'
233 WRITE (i,*)
'PARSOLVER=F : SERIAL'
235 WRITE (i,*)
'PARFUNCTISL :', parfunctisl
236 WRITE (i,*)
'COLUMN SCALING :',
lcolscale
237 WRITE (i,
'(1x,a,L2,a,i2)')
'PARGMRES :', pargmres,
240 WRITE (i,*)
'OUTPUT_TIMINGS :', output_timings
243 WRITE (i,101)
' TIME DIVB : ', time_divb
244 WRITE (i,101)
' TIME DIVJ : ', time_divj
245 WRITE (i,101)
' TIME BGRADP : ', time_bgradp
246 WRITE (i,101)
' TIME BDOTJ : ', time_bdotj
248 WRITE (i,102)
' M (block size) :',
mblk_size
249 WRITE (i,102)
' N (block rows) :', ns_i
250 WRITE (i,102)
' P (processors) :', nprocs
253 101
FORMAT(a,1p,e10.3)
259 IF (
lverbose) print *,
' Writing output to "siesta_profiles.txt" is finished!'
260 CLOSE (unit=unit_out)
266 CALL dealloc_quantities
268 CALL dealloc_diagnostics
275 CALL blacs_barrier(icontxt,
'All')
276 CALL blacs_gridexit(icontxt)
279 IF ((myrow.EQ.0) .AND. (mycol.EQ.0))
THEN
285 WRITE(tofu,*)
'Called finalizeRemap and Finalize'
289 CALL finalize(finalize_mpi)
296 1000
FORMAT(/,
' nprecon: ',i3,
' LM parameter: ',1pe9.2,
' mu||: ',1pe9.2
297 ' Symmetry Index: ',1pe9.2)
298 1001
FORMAT(/,
'==============================',14x,
'======================='
300 /,
' TIMING INFORMATION ',14x,
' RMS BOUNDARY FORCES'
302 /,
'==============================',14x,
'======================='
303 1002
FORMAT(
' Total runtime : ', f12.3,15x,
'fs(1,m=1) :',1pe10.2/,
304 ' Initialization : ',0pf12.3,15x,
'fs(2,m=1) :',1pe10.2/,
305 ' Diagonal prec : ',0pf12.3,15x,
'fs(2,m!=1) :',1pe10.2/,
306 ' Compute blocks : ',0pf12.3,15x,
'fu(1,m=1) :',1pe10.2/,
307 ' Factor blocks : ',0pf12.3,15x,
'fu(2,m=1) :',1pe10.2/,
308 ' Toijsp : ',0pf12.3,15x,
'fu(2,m!=1) :',1pe10.2/,
309 ' Tomnsp : ',0pf12.3,/,
310 ' GMRES : ',0pf12.3,/,
311 ' Conj Gradient : ',0pf12.3,//,
313 ' Update Pressure: ',0pf12.3,15x,
'fv(1,m=0) :',1pe10.2/,
314 ' Update Bfield : ',0pf12.3,15x,
'fv(2,m=0) :',1pe10.2/,
315 ' CV Currents : ',0pf12.3,15x,
'fv(2,m!=0) :',1pe10.2/,
316 ' Force Harmonics: ',0pf12.3,15x,
'fu(ns) :',1pe10.2/,
317 ' Update Force : ',0pf12.3,15x,
'fu(ns-1) :',1pe10.2/,
318 ' Update UpperV : ',0pf12.3,15x,
'fv(ns) :',1pe10.2/,
319 ' Update State : ',0pf12.3,15x,
'fv(ns-1) :',1pe10.2/,
320 ' Funct Island : ',0pf12.3/,
321 ' Apply Precon : ',0pf12.3/,
322 ' Add Perturb : ',0pf12.3/,
323 ' Init State : ',0pf12.3,
324 /,
'==============================',14x,
'======================='
325 END SUBROUTINE siesta_run_destruct
338 SUBROUTINE siesta_run_set_vmec(this)
342 USE quantities,
ONLY: init_quantities, init_fields
348 USE evolution,
ONLY: init_evolution
349 USE nscalingtools,
ONLY: initremap
354 TYPE (siesta_run_class),
INTENT(inout) :: this
365 CALL assert_eq(0, istat,
'LoadRZL error in siesta_run_set_vmec')
370 CALL grid_extender(
wout_file,
'quad', istat)
378 CALL initremap(mpol, ntor, ns, nprocs, iam)
399 SUBROUTINE siesta_run_set_restart(this)
406 USE descriptor_mod,
ONLY: iam, nprocs
407 USE evolution,
ONLY: init_evolution
408 USE nscalingtools,
ONLY: initremap
410 USE hessian,
ONLY: inithess
415 TYPE (siesta_run_class),
INTENT(inout) :: this
452 SUBROUTINE siesta_run_converge(this)
453 USE evolution,
ONLY: converge_diagonal, converge_blocks
454 USE descriptor_mod,
ONLY: diagonaldone, iam
460 TYPE (siesta_run_class),
INTENT(inout) :: this
464 diagonaldone = .false.
466 diagonaldone = .true.