Line data Source code
1 : !--------------------------------------------------------------------------------------------------!
2 : ! CP2K: A general program to perform molecular dynamics simulations !
3 : ! Copyright 2000-2024 CP2K developers group <https://cp2k.org> !
4 : ! !
5 : ! SPDX-License-Identifier: GPL-2.0-or-later !
6 : !--------------------------------------------------------------------------------------------------!
7 :
8 : ! **************************************************************************************************
9 : !> \brief Interface to the PEXSI library, providing wrappers for all PEXSI
10 : !> routines that are called inside CP2K. Requires PEXSI version 0.10.x.
11 : !> \par History
12 : !> 2014.12 created [Patrick Seewald]
13 : !> \author Patrick Seewald
14 : ! **************************************************************************************************
15 : MODULE pexsi_interface
16 :
17 : #if defined(__LIBPEXSI)
18 : USE f_ppexsi_interface, ONLY: f_ppexsi_dft_driver, &
19 : f_ppexsi_load_real_hs_matrix, &
20 : f_ppexsi_options, &
21 : f_ppexsi_plan_finalize, &
22 : f_ppexsi_plan_initialize, &
23 : f_ppexsi_retrieve_real_dft_matrix, &
24 : f_ppexsi_set_default_options
25 : #endif
26 : #if defined(__HAS_IEEE_EXCEPTIONS)
27 : USE ieee_exceptions, ONLY: ieee_get_halting_mode, &
28 : ieee_set_halting_mode, &
29 : ieee_all
30 : #endif
31 : USE kinds, ONLY: int_8, &
32 : real_8
33 : USE ISO_C_BINDING, ONLY: C_INTPTR_T
34 : USE message_passing, ONLY: mp_comm_type
35 : #include "./base/base_uses.f90"
36 :
37 : IMPLICIT NONE
38 :
39 : PRIVATE
40 :
41 : CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'pexsi_interface'
42 :
43 : PUBLIC :: cp_pexsi_options, cp_pexsi_plan_initialize, &
44 : cp_pexsi_load_real_hs_matrix, cp_pexsi_dft_driver, &
45 : cp_pexsi_retrieve_real_dft_matrix, cp_pexsi_plan_finalize, &
46 : cp_pexsi_set_options, cp_pexsi_get_options, cp_pexsi_set_default_options
47 :
48 : TYPE cp_pexsi_options
49 : PRIVATE
50 : #if defined(__LIBPEXSI)
51 : TYPE(f_ppexsi_options) :: options
52 : #else
53 : INTEGER :: unused = -1
54 : #endif
55 : END TYPE cp_pexsi_options
56 :
57 : CONTAINS
58 :
59 : ! **************************************************************************************************
60 : !> \brief Set PEXSI internal options
61 : !> \param pexsi_options ...
62 : !> \param temperature ...
63 : !> \param gap ...
64 : !> \param deltaE ...
65 : !> \param numPole ...
66 : !> \param isInertiaCount ...
67 : !> \param maxPEXSIIter ...
68 : !> \param muMin0 ...
69 : !> \param muMax0 ...
70 : !> \param mu0 ...
71 : !> \param muInertiaTolerance ...
72 : !> \param muInertiaExpansion ...
73 : !> \param muPEXSISafeGuard ...
74 : !> \param numElectronPEXSITolerance ...
75 : !> \param matrixType ...
76 : !> \param isSymbolicFactorize ...
77 : !> \param ordering ...
78 : !> \param rowOrdering ...
79 : !> \param npSymbFact ...
80 : !> \param verbosity ...
81 : ! **************************************************************************************************
82 334 : SUBROUTINE cp_pexsi_set_options(pexsi_options, temperature, gap, deltaE, numPole, &
83 : isInertiaCount, maxPEXSIIter, muMin0, muMax0, mu0, &
84 : muInertiaTolerance, muInertiaExpansion, &
85 : muPEXSISafeGuard, numElectronPEXSITolerance, &
86 : matrixType, isSymbolicFactorize, ordering, rowOrdering, &
87 : npSymbFact, verbosity)
88 :
89 : TYPE(cp_pexsi_options), INTENT(INOUT) :: pexsi_options
90 : REAL(KIND=real_8), INTENT(IN), OPTIONAL :: temperature, gap, deltaE
91 : INTEGER, INTENT(IN), OPTIONAL :: numPole, isInertiaCount, &
92 : maxPEXSIIter
93 : REAL(KIND=real_8), INTENT(IN), OPTIONAL :: muMin0, muMax0, mu0, &
94 : muInertiaTolerance, muInertiaExpansion, muPEXSISafeGuard, &
95 : numElectronPEXSITolerance
96 : INTEGER, INTENT(IN), OPTIONAL :: matrixType, &
97 : isSymbolicFactorize, &
98 : ordering, rowOrdering, npSymbFact, &
99 : verbosity
100 :
101 : #if defined(__LIBPEXSI)
102 334 : IF (PRESENT(temperature)) pexsi_options%options%temperature = temperature
103 334 : IF (PRESENT(gap)) pexsi_options%options%gap = gap
104 334 : IF (PRESENT(deltaE)) pexsi_options%options%deltaE = deltaE
105 334 : IF (PRESENT(numPole)) pexsi_options%options%numPole = numPole
106 334 : IF (PRESENT(isInertiaCount)) pexsi_options%options%isInertiaCount = isInertiaCount
107 334 : IF (PRESENT(maxPEXSIIter)) pexsi_options%options%maxPEXSIIter = maxPEXSIIter
108 334 : IF (PRESENT(muMin0)) pexsi_options%options%muMin0 = muMin0
109 334 : IF (PRESENT(muMax0)) pexsi_options%options%muMax0 = muMax0
110 334 : IF (PRESENT(mu0)) pexsi_options%options%mu0 = mu0
111 334 : IF (PRESENT(muInertiaTolerance)) &
112 8 : pexsi_options%options%muInertiaTolerance = muInertiaTolerance
113 334 : IF (PRESENT(muInertiaExpansion)) &
114 8 : pexsi_options%options%muInertiaExpansion = muInertiaExpansion
115 334 : IF (PRESENT(muPEXSISafeGuard)) &
116 8 : pexsi_options%options%muPEXSISafeGuard = muPEXSISafeGuard
117 334 : IF (PRESENT(numElectronPEXSITolerance)) &
118 96 : pexsi_options%options%numElectronPEXSITolerance = numElectronPEXSITolerance
119 334 : IF (PRESENT(matrixType)) pexsi_options%options%matrixType = matrixType
120 334 : IF (PRESENT(isSymbolicFactorize)) &
121 28 : pexsi_options%options%isSymbolicFactorize = isSymbolicFactorize
122 334 : IF (PRESENT(ordering)) pexsi_options%options%ordering = ordering
123 334 : IF (PRESENT(rowOrdering)) pexsi_options%options%rowOrdering = rowOrdering
124 334 : IF (PRESENT(npSymbFact)) pexsi_options%options%npSymbFact = npSymbFact
125 334 : IF (PRESENT(verbosity)) pexsi_options%options%verbosity = verbosity
126 : #else
127 : MARK_USED(pexsi_options)
128 : MARK_USED(temperature)
129 : MARK_USED(gap)
130 : MARK_USED(deltaE)
131 : MARK_USED(numPole)
132 : MARK_USED(isInertiaCount)
133 : MARK_USED(maxPEXSIIter)
134 : MARK_USED(muMin0)
135 : MARK_USED(muMax0)
136 : MARK_USED(mu0)
137 : MARK_USED(muInertiaTolerance)
138 : MARK_USED(muInertiaExpansion)
139 : MARK_USED(muPEXSISafeGuard)
140 : MARK_USED(numElectronPEXSITolerance)
141 : MARK_USED(matrixType)
142 : MARK_USED(isSymbolicFactorize)
143 : MARK_USED(ordering)
144 : MARK_USED(rowOrdering)
145 : MARK_USED(npSymbFact)
146 : MARK_USED(verbosity)
147 : CPABORT("Requires linking to the PEXSI library.")
148 : #endif
149 :
150 : ! Additional PEXSI parameters and their defaults not made available here
151 : ! because CP2K should always use PEXSI's defaults:
152 : ! isConstructCommPattern (=?, pexsi does not even use it)
153 : ! symmetric (=1)
154 : ! transpose (=0)
155 334 : END SUBROUTINE cp_pexsi_set_options
156 :
157 : ! **************************************************************************************************
158 : !> \brief Access PEXSI internal options
159 : !> \param pexsi_options ...
160 : !> \param temperature ...
161 : !> \param gap ...
162 : !> \param deltaE ...
163 : !> \param numPole ...
164 : !> \param isInertiaCount ...
165 : !> \param maxPEXSIIter ...
166 : !> \param muMin0 ...
167 : !> \param muMax0 ...
168 : !> \param mu0 ...
169 : !> \param muInertiaTolerance ...
170 : !> \param muInertiaExpansion ...
171 : !> \param muPEXSISafeGuard ...
172 : !> \param numElectronPEXSITolerance ...
173 : !> \param matrixType ...
174 : !> \param isSymbolicFactorize ...
175 : !> \param ordering ...
176 : !> \param rowOrdering ...
177 : !> \param npSymbFact ...
178 : !> \param verbosity ...
179 : ! **************************************************************************************************
180 120 : SUBROUTINE cp_pexsi_get_options(pexsi_options, temperature, gap, deltaE, numPole, &
181 : isInertiaCount, maxPEXSIIter, muMin0, muMax0, mu0, &
182 : muInertiaTolerance, muInertiaExpansion, &
183 : muPEXSISafeGuard, numElectronPEXSITolerance, &
184 : matrixType, isSymbolicFactorize, ordering, rowOrdering, &
185 : npSymbFact, verbosity)
186 : TYPE(cp_pexsi_options), INTENT(IN) :: pexsi_options
187 : REAL(KIND=real_8), INTENT(OUT), OPTIONAL :: temperature, gap, deltaE
188 : INTEGER, INTENT(OUT), OPTIONAL :: numPole, isInertiaCount, &
189 : maxPEXSIIter
190 : REAL(KIND=real_8), INTENT(OUT), OPTIONAL :: muMin0, muMax0, mu0, &
191 : muInertiaTolerance, muInertiaExpansion, muPEXSISafeGuard, &
192 : numElectronPEXSITolerance
193 : INTEGER, INTENT(OUT), OPTIONAL :: matrixType, &
194 : isSymbolicFactorize, &
195 : ordering, rowOrdering, npSymbFact, &
196 : verbosity
197 :
198 : #if defined(__LIBPEXSI)
199 120 : IF (PRESENT(temperature)) temperature = pexsi_options%options%temperature
200 120 : IF (PRESENT(gap)) gap = pexsi_options%options%gap
201 120 : IF (PRESENT(deltaE)) deltaE = pexsi_options%options%deltaE
202 120 : IF (PRESENT(numPole)) numPole = pexsi_options%options%numPole
203 120 : IF (PRESENT(isInertiaCount)) isInertiaCount = pexsi_options%options%isInertiaCount
204 120 : IF (PRESENT(maxPEXSIIter)) maxPEXSIIter = pexsi_options%options%maxPEXSIIter
205 120 : IF (PRESENT(muMin0)) muMin0 = pexsi_options%options%muMin0
206 120 : IF (PRESENT(muMax0)) muMax0 = pexsi_options%options%muMax0
207 120 : IF (PRESENT(mu0)) mu0 = pexsi_options%options%mu0
208 120 : IF (PRESENT(muInertiaTolerance)) &
209 4 : muInertiaTolerance = pexsi_options%options%muInertiaTolerance
210 120 : IF (PRESENT(muInertiaExpansion)) &
211 4 : muInertiaExpansion = pexsi_options%options%muInertiaExpansion
212 120 : IF (PRESENT(muPEXSISafeGuard)) &
213 4 : muPEXSISafeGuard = pexsi_options%options%muPEXSISafeGuard
214 120 : IF (PRESENT(numElectronPEXSITolerance)) &
215 94 : numElectronPEXSITolerance = pexsi_options%options%numElectronPEXSITolerance
216 120 : IF (PRESENT(matrixType)) matrixType = pexsi_options%options%matrixType
217 120 : IF (PRESENT(isSymbolicFactorize)) &
218 94 : isSymbolicFactorize = pexsi_options%options%isSymbolicFactorize
219 120 : IF (PRESENT(ordering)) ordering = pexsi_options%options%ordering
220 120 : IF (PRESENT(rowOrdering)) rowOrdering = pexsi_options%options%rowOrdering
221 120 : IF (PRESENT(npSymbFact)) npSymbFact = pexsi_options%options%npSymbFact
222 120 : IF (PRESENT(verbosity)) verbosity = pexsi_options%options%verbosity
223 : #else
224 : MARK_USED(pexsi_options)
225 : ! assign intent-out arguments to silence compiler warnings
226 : IF (PRESENT(temperature)) temperature = 0.0_real_8
227 : IF (PRESENT(gap)) gap = 0.0_real_8
228 : IF (PRESENT(deltaE)) deltaE = 0.0_real_8
229 : IF (PRESENT(numPole)) numPole = -1
230 : IF (PRESENT(isInertiaCount)) isInertiaCount = -1
231 : IF (PRESENT(maxPEXSIIter)) maxPEXSIIter = -1
232 : IF (PRESENT(muMin0)) muMin0 = 0.0_real_8
233 : IF (PRESENT(muMax0)) muMax0 = 0.0_real_8
234 : IF (PRESENT(mu0)) mu0 = 0.0_real_8
235 : IF (PRESENT(muInertiaTolerance)) muInertiaTolerance = 0.0_real_8
236 : IF (PRESENT(muInertiaExpansion)) muInertiaExpansion = 0.0_real_8
237 : IF (PRESENT(muPEXSISafeGuard)) muPEXSISafeGuard = 0.0_real_8
238 : IF (PRESENT(numElectronPEXSITolerance)) numElectronPEXSITolerance = 0.0_real_8
239 : IF (PRESENT(matrixType)) matrixType = -1
240 : IF (PRESENT(isSymbolicFactorize)) isSymbolicFactorize = -1
241 : IF (PRESENT(ordering)) ordering = -1
242 : IF (PRESENT(rowOrdering)) rowOrdering = -1
243 : IF (PRESENT(npSymbFact)) npSymbFact = -1
244 : IF (PRESENT(verbosity)) verbosity = -1
245 : CPABORT("Requires linking to the PEXSI library.")
246 : #endif
247 120 : END SUBROUTINE cp_pexsi_get_options
248 :
249 : ! **************************************************************************************************
250 : !> \brief ...
251 : !> \param pexsi_options ...
252 : ! **************************************************************************************************
253 8 : SUBROUTINE cp_pexsi_set_default_options(pexsi_options)
254 : TYPE(cp_pexsi_options), INTENT(OUT) :: pexsi_options
255 :
256 : #if defined(__LIBPEXSI)
257 8 : CALL f_ppexsi_set_default_options(pexsi_options%options)
258 : #else
259 : CPABORT("Requires linking to the PEXSI library.")
260 : #endif
261 8 : END SUBROUTINE cp_pexsi_set_default_options
262 :
263 : ! **************************************************************************************************
264 : !> \brief ...
265 : !> \param comm ...
266 : !> \param numProcRow ...
267 : !> \param numProcCol ...
268 : !> \param outputFileIndex ...
269 : !> \return ...
270 : ! **************************************************************************************************
271 8 : FUNCTION cp_pexsi_plan_initialize(comm, numProcRow, numProcCol, outputFileIndex)
272 : TYPE(mp_comm_type), INTENT(IN) :: comm
273 : INTEGER, INTENT(IN) :: numProcRow, numProcCol, &
274 : outputFileIndex
275 : INTEGER(KIND=C_INTPTR_T) :: cp_pexsi_plan_initialize
276 :
277 : #if defined(__LIBPEXSI)
278 : CHARACTER(LEN=*), PARAMETER :: routineN = 'cp_pexsi_plan_initialize'
279 : INTEGER :: info, handle
280 :
281 8 : CALL timeset(routineN, handle)
282 : cp_pexsi_plan_initialize = f_ppexsi_plan_initialize(comm%get_handle(), numProcRow, &
283 8 : numProcCol, outputFileIndex, info)
284 8 : IF (info .NE. 0) &
285 0 : CPABORT("Pexsi returned an error. Consider logPEXSI0 for details.")
286 8 : CALL timestop(handle)
287 : #else
288 : MARK_USED(comm)
289 : MARK_USED(numProcRow)
290 : MARK_USED(numProcCol)
291 : MARK_USED(outputFileIndex)
292 : cp_pexsi_plan_initialize = 0
293 : CPABORT("Requires linking to the PEXSI library.")
294 : #endif
295 8 : END FUNCTION cp_pexsi_plan_initialize
296 :
297 : ! **************************************************************************************************
298 : !> \brief ...
299 : !> \param plan ...
300 : !> \param pexsi_options ...
301 : !> \param nrows ...
302 : !> \param nnz ...
303 : !> \param nnzLocal ...
304 : !> \param numColLocal ...
305 : !> \param colptrLocal ...
306 : !> \param rowindLocal ...
307 : !> \param HnzvalLocal ...
308 : !> \param isSIdentity ...
309 : !> \param SnzvalLocal ...
310 : ! **************************************************************************************************
311 188 : SUBROUTINE cp_pexsi_load_real_hs_matrix(plan, pexsi_options, nrows, nnz, &
312 : nnzLocal, numColLocal, colptrLocal, &
313 : rowindLocal, HnzvalLocal, isSIdentity, &
314 : SnzvalLocal)
315 : INTEGER(KIND=C_INTPTR_T), INTENT(IN) :: plan
316 : TYPE(cp_pexsi_options), INTENT(IN) :: pexsi_options
317 : INTEGER, INTENT(IN) :: nrows, nnz, nnzLocal, &
318 : numColLocal, colptrLocal(*), &
319 : rowindLocal(*)
320 : REAL(KIND=real_8), INTENT(IN) :: HnzvalLocal(*)
321 : INTEGER, INTENT(IN) :: isSIdentity
322 : REAL(KIND=real_8), INTENT(IN) :: SnzvalLocal(*)
323 :
324 : #if defined(__LIBPEXSI)
325 : CHARACTER(LEN=*), PARAMETER :: routineN = 'cp_pexsi_load_real_symmetric_hs_matrix'
326 : INTEGER :: handle, info
327 :
328 94 : CALL timeset(routineN, handle)
329 : CALL f_ppexsi_load_real_hs_matrix(plan, pexsi_options%options, nrows, nnz, nnzLocal, &
330 : numColLocal, colptrLocal, rowindLocal, &
331 94 : HnzvalLocal, isSIdentity, SnzvalLocal, info)
332 94 : IF (info .NE. 0) &
333 0 : CPABORT("Pexsi returned an error. Consider logPEXSI0 for details.")
334 94 : CALL timestop(handle)
335 : #else
336 : MARK_USED(plan)
337 : MARK_USED(pexsi_options)
338 : MARK_USED(nrows)
339 : MARK_USED(nnz)
340 : MARK_USED(nnzLocal)
341 : MARK_USED(numColLocal)
342 : MARK_USED(isSIdentity)
343 : CPABORT("Requires linking to the PEXSI library.")
344 :
345 : ! MARK_USED macro does not work on assumed shape variables
346 : IF (.FALSE.) THEN; DO
347 : IF (colptrLocal(1) > rowindLocal(1) .OR. HnzvalLocal(1) > SnzvalLocal(1)) EXIT
348 : END DO; END IF
349 : #endif
350 94 : END SUBROUTINE cp_pexsi_load_real_hs_matrix
351 :
352 : ! **************************************************************************************************
353 : !> \brief ...
354 : !> \param plan ...
355 : !> \param pexsi_options ...
356 : !> \param numElectronExact ...
357 : !> \param muPEXSI ...
358 : !> \param numElectronPEXSI ...
359 : !> \param muMinInertia ...
360 : !> \param muMaxInertia ...
361 : !> \param numTotalInertiaIter ...
362 : !> \param numTotalPEXSIIter ...
363 : ! **************************************************************************************************
364 188 : SUBROUTINE cp_pexsi_dft_driver(plan, pexsi_options, numElectronExact, muPEXSI, &
365 : numElectronPEXSI, muMinInertia, muMaxInertia, &
366 : numTotalInertiaIter, numTotalPEXSIIter)
367 : INTEGER(KIND=C_INTPTR_T), INTENT(IN) :: plan
368 : TYPE(cp_pexsi_options), INTENT(IN) :: pexsi_options
369 : REAL(KIND=real_8), INTENT(IN) :: numElectronExact
370 : REAL(KIND=real_8), INTENT(out) :: muPEXSI, numElectronPEXSI, &
371 : muMinInertia, muMaxInertia
372 : INTEGER, INTENT(out) :: numTotalInertiaIter, &
373 : numTotalPEXSIIter
374 :
375 : #if defined(__LIBPEXSI)
376 : CHARACTER(LEN=*), PARAMETER :: routineN = 'cp_pexsi_dft_driver'
377 : INTEGER :: handle, info
378 : #if defined(__HAS_IEEE_EXCEPTIONS)
379 : LOGICAL, DIMENSION(5) :: halt
380 : #endif
381 :
382 94 : CALL timeset(routineN, handle)
383 :
384 : ! Unfortuntatelly, some PEXSI kernels raise IEEE754 exceptions.
385 : ! Therefore, we disable floating point traps temporarily.
386 : #if defined(__HAS_IEEE_EXCEPTIONS)
387 : CALL ieee_get_halting_mode(IEEE_ALL, halt)
388 : CALL ieee_set_halting_mode(IEEE_ALL, .FALSE.)
389 : #endif
390 :
391 : CALL f_ppexsi_dft_driver(plan, pexsi_options%options, numElectronExact, muPEXSI, &
392 : numElectronPEXSI, muMinInertia, muMaxInertia, &
393 94 : numTotalInertiaIter, numTotalPEXSIIter, info)
394 :
395 : #if defined(__HAS_IEEE_EXCEPTIONS)
396 : CALL ieee_set_halting_mode(IEEE_ALL, halt)
397 : #endif
398 :
399 94 : IF (info .NE. 0) &
400 0 : CPABORT("Pexsi returned an error. Consider logPEXSI0 for details.")
401 94 : CALL timestop(handle)
402 : #else
403 : MARK_USED(plan)
404 : MARK_USED(numelectronexact)
405 : MARK_USED(pexsi_options)
406 : ! assign intent-out arguments to silence compiler warnings
407 : muPEXSI = 0.0_real_8
408 : numElectronPEXSI = 0.0_real_8
409 : muMinInertia = 0.0_real_8
410 : muMaxInertia = 0.0_real_8
411 : numTotalInertiaIter = -1
412 : numTotalPEXSIIter = -1
413 : CPABORT("Requires linking to the PEXSI library.")
414 : #endif
415 94 : END SUBROUTINE cp_pexsi_dft_driver
416 :
417 : ! **************************************************************************************************
418 : !> \brief ...
419 : !> \param plan ...
420 : !> \param DMnzvalLocal ...
421 : !> \param EDMnzvalLocal ...
422 : !> \param FDMnzvalLocal ...
423 : !> \param totalEnergyH ...
424 : !> \param totalEnergyS ...
425 : !> \param totalFreeEnergy ...
426 : ! **************************************************************************************************
427 188 : SUBROUTINE cp_pexsi_retrieve_real_dft_matrix(plan, DMnzvalLocal, EDMnzvalLocal, &
428 : FDMnzvalLocal, totalEnergyH, &
429 : totalEnergyS, totalFreeEnergy)
430 : INTEGER(KIND=C_INTPTR_T), INTENT(IN) :: plan
431 : REAL(KIND=real_8), INTENT(out) :: DMnzvalLocal(*), EDMnzvalLocal(*), &
432 : FDMnzvalLocal(*), totalEnergyH, totalEnergyS, &
433 : totalFreeEnergy
434 :
435 : #if defined(__LIBPEXSI)
436 : CHARACTER(LEN=*), PARAMETER :: routineN = 'cp_pexsi_retrieve_real_symmetric_dft_matrix'
437 : INTEGER :: handle, info
438 :
439 94 : CALL timeset(routineN, handle)
440 : CALL f_ppexsi_retrieve_real_dft_matrix(plan, DMnzvalLocal, EDMnzvalLocal, &
441 : FDMnzvalLocal, totalEnergyH, &
442 94 : totalEnergyS, totalFreeEnergy, info)
443 94 : IF (info .NE. 0) &
444 0 : CPABORT("Pexsi returned an error. Consider logPEXSI0 for details.")
445 94 : CALL timestop(handle)
446 : #else
447 : MARK_USED(plan)
448 : ! assign intent-out arguments to silence compiler warnings
449 : DMnzvalLocal(1) = 0.0_real_8
450 : EDMnzvalLocal(1) = 0.0_real_8
451 : FDMnzvalLocal(1) = 0.0_real_8
452 : totalEnergyH = 0.0_real_8
453 : totalEnergyS = 0.0_real_8
454 : totalFreeEnergy = 0.0_real_8
455 :
456 : CPABORT("Requires linking to the PEXSI library.")
457 : #endif
458 94 : END SUBROUTINE cp_pexsi_retrieve_real_dft_matrix
459 :
460 : ! **************************************************************************************************
461 : !> \brief ...
462 : !> \param plan ...
463 : ! **************************************************************************************************
464 16 : SUBROUTINE cp_pexsi_plan_finalize(plan)
465 : INTEGER(KIND=C_INTPTR_T), INTENT(IN) :: plan
466 :
467 : #if defined(__LIBPEXSI)
468 : CHARACTER(LEN=*), PARAMETER :: routineN = 'cp_pexsi_plan_finalize'
469 : INTEGER :: info, handle
470 :
471 8 : CALL timeset(routineN, handle)
472 8 : CALL f_ppexsi_plan_finalize(plan, info)
473 8 : IF (info .NE. 0) &
474 0 : CPABORT("Pexsi returned an error. Consider logPEXSI0 for details.")
475 8 : CALL timestop(handle)
476 : #else
477 : MARK_USED(plan)
478 : CPABORT("Requires linking to the PEXSI library.")
479 : #endif
480 8 : END SUBROUTINE
481 :
482 0 : END MODULE pexsi_interface
|