Octopus
ps_hgh.F90
Go to the documentation of this file.
1!! Copyright (C) 2002-2006 M. Marques, A. Castro, A. Rubio, G. Bertsch
2!! Copyright (C) 2020 N. Tancogne-Dejean
3!!
4!! This program is free software; you can redistribute it and/or modify
5!! it under the terms of the GNU General Public License as published by
6!! the Free Software Foundation; either version 2, or (at your option)
7!! any later version.
8!!
9!! This program is distributed in the hope that it will be useful,
10!! but WITHOUT ANY WARRANTY; without even the implied warranty of
11!! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12!! GNU General Public License for more details.
13!!
14!! You should have received a copy of the GNU General Public License
15!! along with this program; if not, write to the Free Software
16!! Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
17!! 02110-1301, USA.
18!!
19
20#include "global.h"
21
22module ps_hgh_oct_m
23
26 use atomic_oct_m
27 use debug_oct_m
28 use global_oct_m
29 use io_oct_m
30 use, intrinsic :: iso_fortran_env
32 use logrid_oct_m
36
37 implicit none
38
39 private
40 public :: &
41 ps_hgh_t, &
42 hgh_init, &
44 hgh_debug, &
45 hgh_end, &
47
51 type ps_hgh_t
52 ! Components are public by default
53
54 character(len=256), private :: title
55 integer, private :: pspdat ! date of creation of PP (DDMMYY)
56 integer, private :: pspcod ! code for the pseudopotential (3 for .hgh)
57 integer, private :: pspxc ! exchange-correlation used to generate the psp
58 integer :: lmax ! Maximum l to use
59 integer, private :: mmax ! Maximum number of points in real space grid
60 real(real64), private :: r2well ! ??
61
62
63 character(len=5), private :: atom_name
64 integer :: z_val
65 real(real64) :: rlocal
66 real(real64), private :: rc(0:3)
67 real(real64), private :: c(1:4)
68 real(real64) :: h(0:3, 1:3, 1:3)
69 real(real64) :: k(0:3, 1:3, 1:3)
70
71 type(valconf_t) :: conf
72 integer :: l_max
73
74 real(real64), allocatable :: vlocal(:)
75 real(real64), allocatable :: kb(:,:,:)
76 real(real64), allocatable :: kbr(:)
77 real(real64), allocatable :: rphi(:,:)
78 real(real64), allocatable, private :: eigen(:)
79
81 type(logrid_t) :: g
82 end type ps_hgh_t
83
84 real(real64), parameter :: eps = 1.0e-8_real64
85
86contains
87
88 ! ---------------------------------------------------------
89 subroutine hgh_init(psp, filename, namespace)
90 type(ps_hgh_t), intent(inout) :: psp
91 character(len=*), intent(in) :: filename
92 type(namespace_t), intent(in) :: namespace
93
94 integer :: iunit, i, np
95 real(real64) :: aa, bb
96
97 push_sub(hgh_init)
98
99 iunit = io_open(trim(filename), action='read', form='formatted', status='old')
100 i = load_params(iunit, psp, namespace)
101 if (i /= 0) then
102 call messages_write('Error reading hgh file')
103 call messages_fatal(namespace=namespace)
104 end if
105 call io_close(iunit)
106
107 ! Finds out psp%l_max. The most special cases are H, He, Li_sc and Be_sc, where psp%l_max = -1.
108 psp%l_max = 0
109 do while(psp%rc(psp%l_max) > 0.01_real64)
110 psp%l_max = psp%l_max + 1
111 if (psp%l_max > 3) exit
112 end do
113 psp%l_max = psp%l_max - 1
114
115 call logrid_find_parameters(namespace, psp%conf%z, aa, bb, np)
116
117 call logrid_init(psp%g, logrid_psf, aa, bb, np)
118
119 ! Allocation of stuff.
120 safe_allocate(psp%vlocal(1:psp%g%nrval))
121 psp%vlocal = m_zero
122 if (psp%l_max >= 0) then
123 safe_allocate(psp%kbr(0:psp%l_max))
124 safe_allocate(psp%kb(1:psp%g%nrval, 0:psp%l_max, 1:3))
125 psp%kbr = m_zero
126 psp%kb = m_zero
127 end if
128
129 pop_sub(hgh_init)
130 end subroutine hgh_init
131
132
133 ! ---------------------------------------------------------
134 subroutine hgh_end(psp)
135 type(ps_hgh_t), intent(inout) :: psp
136
137 push_sub(hgh_end)
138
139 if (psp%l_max >= 0) then
140 safe_deallocate_a(psp%kbr)
141 safe_deallocate_a(psp%kb)
142 end if
143 safe_deallocate_a(psp%vlocal)
144 safe_deallocate_a(psp%rphi)
145 safe_deallocate_a(psp%eigen)
146 call logrid_end(psp%g)
148 pop_sub(hgh_end)
149 end subroutine hgh_end
152 ! ---------------------------------------------------------
153 subroutine hgh_process(psp, namespace)
154 type(ps_hgh_t), intent(inout) :: psp
155 type(namespace_t), intent(in) :: namespace
157 integer :: l, i, ierr
159 push_sub(hgh_process)
161 safe_allocate(psp%rphi(1:psp%g%nrval, 1:psp%conf%p))
162 safe_allocate(psp%eigen(1:psp%conf%p))
163 psp%rphi = m_zero
164 psp%eigen = m_zero
166
167 ! Fixes the local potential
168 call vlocalr_scalar(psp%g%rofi, psp%g%nrval, psp, psp%vlocal)
170 ! And the projectors
171 do l = 0, psp%l_max
172 do i = 1, 3
173 call projectorr_scalar(psp%g%rofi, psp%g%nrval, psp, i, l, psp%kb(:, l, i))
174 end do
175 end do
176
177 ! get the pseudoatomic eigenfunctions (WARNING: This is not correctly done yet: "some" wavefunctions
178 ! are obtained, but not the real ones!!!
179 call solve_schroedinger(psp, ierr, namespace)
180 if (ierr /= 0) then ! If the wavefunctions could not be found, we set its number to zero.
181 write(message(1),'(a)') 'The algorithm that calculates atomic wavefunctions could not'
182 write(message(2),'(a)') 'do its job. The program will continue, but expect poor'
183 write(message(3),'(a)') 'convergence properties.'
184 call messages_warning(3, namespace=namespace)
185 psp%conf%p = 0
186 end if
187
188 ! Define the KB-projector cut-off radii
189 call get_cutoff_radii(psp)
190
191 pop_sub(hgh_process)
192 end subroutine hgh_process
193
194 ! ---------------------------------------------------------
195 subroutine hgh_get_eigen(psp, eigen)
196 type(ps_hgh_t), intent(in) :: psp
197 real(real64), intent(out) :: eigen(:,:)
198
199 integer :: i
200
201 push_sub(hgh_get_eigen)
202
203 do i = 1, psp%conf%p
204 eigen(i, :) = psp%eigen(i)
205 end do
206
207 pop_sub(hgh_get_eigen)
208 end subroutine hgh_get_eigen
209
210 ! ---------------------------------------------------------
211 function load_params(unit, params, namespace)
212 integer, intent(in) :: unit ! where to read from
213 type(ps_hgh_t), intent(out) :: params ! obvious
214 type(namespace_t), intent(in) :: namespace
215
216 integer :: load_params ! 0 if success,
217 ! 1 otherwise.
218
219 integer :: i, iostat, j, k, nn, nnonloc, lloc
220 character(len=VALCONF_STRING_LENGTH) :: line
221
222 push_sub(load_params)
223
224 ! Set initially everything to zero.
225 params%c(1:4) = m_zero
226 params%rlocal = m_zero
227 params%rc = m_zero
228 params%h = m_zero
229 params%k = m_zero
230
231 read(unit, *) params%title
232 read(unit, *) params%conf%z, params%z_val, params%pspdat
233 read(unit, *, iostat=iostat) params%pspcod, params%pspxc, params%l_max, lloc, params%mmax, params%r2well
234
235 select case (params%pspcod)
236 case (3)
237
238 ! Reads the file in a hopefully smart way
239 iostat = 1
240 j = 5
241 read(unit,'(a)') line
242 do while((iostat /= 0) .and. (j > 0))
243 j = j - 1
244 read(line, *, iostat=iostat) params%rlocal, params%c(1:j)
245 end do
246 if (j<1) read(line, *, iostat=iostat) params%atom_name, params%z_val, params%rlocal
247 if (iostat /= 0) then
248 load_params = 1
249 pop_sub(load_params)
250 return
251 end if
252
253 read(unit,'(a)', iostat = iostat) line
254 if (iostat /= 0) then
255 load_params = 0
256 pop_sub(load_params)
257 return
258 end if
259 iostat = 1
260 j = 4
261 do while((iostat /= 0) .and. (j > 0))
262 j = j - 1
263 read(line, *, iostat=iostat) params%rc(0), (params%h(0, i, i), i = 1, j)
264 end do
265 if (j < 0) then
266 load_params = 2
267 pop_sub(load_params)
268 return
269 end if
270
271 kloop: do k = 1, 3
272 read(unit, '(a)', iostat = iostat) line
273 if (iostat /= 0) exit kloop
274 iostat = 1
275 j = 4
276 do while((iostat /= 0) .and. (j > 0))
277 j = j - 1
278 read(line, *, iostat = iostat) params%rc(k), (params%h(k, i, i), i = 1, j)
279 end do
280 if (abs(params%rc(k)) <= m_epsilon) exit kloop
281 read(unit, '(a)') line
282 iostat = 1
283 j = 4
284 do while((iostat /= 0) .and. (j>0))
285 j = j - 1
286 read(line, *, iostat = iostat) (params%k(k, i, i), i = 1, 3)
287 end do
288 end do kloop
289
290 ! Fill in the rest of the parameter matrices...
291 params%h(0, 1, 2) = -m_half * sqrt(m_three/m_five) * params%h(0, 2, 2)
292 params%h(0, 1, 3) = m_half * sqrt(m_five/21.0_real64) * params%h(0, 3, 3)
293 params%h(0, 2, 3) = -m_half * sqrt(100.0_real64/63.0_real64) * params%h(0, 3, 3)
294 params%h(1, 1, 2) = -m_half * sqrt(m_five/7.0_real64) * params%h(1, 2, 2)
295 params%h(1, 1, 3) = m_one/6.0_real64 * sqrt(35.0_real64/11.0_real64) * params%h(1, 3, 3)
296 params%h(1, 2, 3) = -m_one/6.0_real64 * (14.0_real64 / sqrt(11.0_real64)) * params%h(1, 3, 3)
297 params%h(2, 1, 2) = -m_half * sqrt(7.0_real64/9.0_real64) * params%h(2, 2, 2)
298 params%h(2, 1, 3) = m_half * sqrt(63.0_real64/143.0_real64) * params%h(2, 3, 3)
299 params%h(2, 2, 3) = -m_half * (18.0_real64/sqrt(143.0_real64)) * params%h(2, 3, 3)
300
301 params%k(0, 1, 2) = -m_half * sqrt(m_three/m_five) * params%k(0, 2, 2)
302 params%k(0, 1, 3) = m_half * sqrt(m_five/21.0_real64) * params%k(0, 3, 3)
303 params%k(0, 2, 3) = -m_half * sqrt(100.0_real64/63.0_real64) * params%k(0, 3, 3)
304 params%k(1, 1, 2) = -m_half * sqrt(m_five/7.0_real64) * params%k(1, 2, 2)
305 params%k(1, 1, 3) = m_one/6.0_real64 * sqrt(35.0_real64/11.0_real64) * params%k(1, 3, 3)
306 params%k(1, 2, 3) = -m_one/6.0_real64 * (14.0_real64 / sqrt(11.0_real64)) * params%k(1, 3, 3)
307 params%k(2, 1, 2) = -m_half * sqrt(7.0_real64/9.0_real64) * params%k(2, 2, 2)
308 params%k(2, 1, 3) = m_half * sqrt(63.0_real64/143.0_real64) * params%k(2, 3, 3)
309 params%k(2, 2, 3) = -m_half * (18.0_real64/sqrt(143.0_real64)) * params%k(2, 3, 3)
310
311
312 case (10)
313
314 read(unit, *) params%rlocal, nn, params%c(1)
315 read(unit, *) nnonloc
316 read(unit, '(a)', iostat = iostat) line
317 kloop2 : do k = 0, 3
318 if (iostat /= 0) exit kloop2
319 iostat = 1
320 j = 4
321 do while((iostat /= 0) .and. (j > 0))
322 j = j - 1
323 read(line, *, iostat = iostat) params%rc(k), nn, (params%h(k, 1, i), i = 1, j)
324 end do
325 if (abs(params%rc(k)) <= m_epsilon) exit kloop2
326 read(unit, '(a)') line
327 select case (nn)
328 case (3)
329 read(line, *) (params%h(1, 2, i), i = 2, 3)
330 read(unit, '(a)') line
331 read(line, *) params%h(1, 3, 3)
332 !Reading the k matrix, if possible
333 read(unit, '(a)', iostat=iostat) line
334 if (iostat /= 0) exit kloop2
335 read(line, *, iostat=iostat) (params%k(1, 1, i), i = 1, 3)
336 if (iostat /= 0) continue !No k matrix
337 read(unit, '(a)') line
338 read(line, *) (params%k(1, 2, i), i = 2, 3)
339 read(unit, '(a)') line
340 read(line, *) params%k(1, 3, 3)
341 read(unit, '(a)', iostat = iostat) line
342 case (2)
343 read(line, *) params%h(0, 2, 2)
344 !Reading the k matrix, if possible
345 read(unit, '(a)', iostat=iostat) line
346 if (iostat /= 0) exit kloop2
347 read(line, *, iostat=iostat) (params%k(1, 1, i), i = 1, 2)
348 if (iostat /= 0) continue !No k matrix
349 read(unit, '(a)') line
350 read(line, *) params%k(1, 2, 2)
351 read(unit, '(a)', iostat = iostat) line
352 case default
353 message(1) = "Error parsing the pseudopotential"
354 call messages_fatal(1, namespace=namespace)
355 end select
356 end do kloop2
357
358 case default
359 message(1) = "Inconsistency in pseudopotential file:"
360 write(message(2),'(a,i2)') " expecting pspcod = 3, but found ", params%pspcod
361 call messages_fatal(2, namespace=namespace)
362 end select
363
364
365 ! Parameters are symmetric.
366 do k = 0, 3
367 do i = 1, 3
368 do j = i + 1, 3
369 params%h(k, j, i) = params%h(k, i, j)
370 params%k(k, j, i) = params%k(k, i, j)
371 end do
372 end do
373 end do
374
375 load_params = 0
376 pop_sub(load_params)
377 end function load_params
378
379
380 ! ---------------------------------------------------------
381 subroutine get_cutoff_radii(psp)
382 type(ps_hgh_t), intent(inout) :: psp
383
384 integer :: ir, l, i
385 real(real64) :: dincv, tmp
386 real(real64), parameter :: threshold = 1.0e-4_real64
387
388 push_sub(get_cutoff_radii)
389
390 do l = 0, psp%l_max
391 tmp = m_zero
392 do i = 1, 3
393 do ir = psp%g%nrval, 2, -1
394 dincv = abs(psp%kb(ir, l, i))
395 if (dincv > threshold) exit
396 end do
397 tmp = psp%g%rofi(ir + 1)
398 psp%kbr(l) = max(tmp, psp%kbr(l))
399 end do
400 end do
401
402 pop_sub(get_cutoff_radii)
403 end subroutine get_cutoff_radii
404
405
406 ! ---------------------------------------------------------
407 ! Local pseudopotential, both in real and reciprocal space.
408 ! See Eq. (1)
409 subroutine vlocalr_scalar(r, np, p, vloc)
410 type(ps_hgh_t), intent(in) :: p
411 real(real64), intent(in) :: r(:)
412 integer, intent(in) :: np
413 real(real64), intent(inout) :: vloc(:)
414
415 integer :: ip
416 real(real64) :: r1, r2
417
418 ! The tolerance is set such that |erf(x/sqrt(2))-2*x/sqrt(2*pi)| is below 2e-16
419 ! This leads to a tolerance of 1e-5.
420 ! However, this values produces an arithmetic error for GSL so it is increase to 5e-5
421 real(real64), parameter :: tol = 5e-5_real64
422
423 push_sub(vlocalr_scalar)
424
425 do ip = 1, np
426 r1 = r(ip)/p%rlocal
427
428 if (r1 < tol) then
429 vloc(ip) = -(m_two * p%z_val) / (sqrt(m_two * m_pi) * p%rlocal) + p%c(1)
430 else
431 r2 = r1**2
432
433 vloc(ip) = -(p%z_val / r(ip)) * loct_erf(r1 / sqrt(m_two))
434 if(r2 < m_two * m_max_exp_arg) then !Else we are getting an underflow
435 vloc(ip) = vloc(ip) + exp(-m_half*r2) * (p%c(1) + r2*(p%c(2) + r2*(p%c(3) + p%c(4)*r2)))
436 end if
437 end if
438 end do
439
440 pop_sub(vlocalr_scalar)
441 end subroutine vlocalr_scalar
442
443
444 ! ---------------------------------------------------------
445 ! Projector in real space, see Eq. 3
446 subroutine projectorr_scalar(r, np, p, i, l, proj)
447 type(ps_hgh_t), intent(in) :: p
448 real(real64), intent(in) :: r(:)
449 integer, intent(in) :: np
450 integer, intent(in) :: i
451 integer, intent(in) :: l
452 real(real64), intent(inout) :: proj(:)
453
454 integer :: ip
455 real(real64) :: x, y, rr, arg
456
457 push_sub(projectorr_scalar)
458
459 x = l + real(4*i-1, real64) / m_two
460 y = loct_gamma(x)
461 x = sqrt(y)
462 rr = m_one
463
464 do ip = 1, np
465
466 if (l /= 0 .or. i /= 1) then
467 rr = r(ip) ** (l + 2*(i-1))
468 end if
469
470 arg = -r(ip)**2/(m_two*p%rc(l)**2)
471 if(arg > m_min_exp_arg) then
472 proj(ip) = sqrt(m_two) * rr * exp(-r(ip)**2/(m_two*p%rc(l)**2)) / &
473 (p%rc(l)**(l + real(4*i-1, real64) / m_two) * x)
474 else
475 proj(ip) = m_zero
476 end if
477 end do
478
479 pop_sub(projectorr_scalar)
480 end subroutine projectorr_scalar
481
482
483 ! ---------------------------------------------------------
484 subroutine solve_schroedinger(psp, ierr, namespace)
485 type(ps_hgh_t), intent(inout) :: psp
486 integer, intent(out) :: ierr
487 type(namespace_t), intent(in) :: namespace
488
489 integer :: iter, ir, l, nnode, nprin, i, j, irr, n, k
490 real(real64) :: vtot, a2b4, diff, nonl
491 real(real64), allocatable :: prev(:, :), rho(:, :), ve(:, :)
492 real(real64), parameter :: tol = 1.0e-4_real64
493 real(real64) :: e, z, dr, rmax
494 real(real64), allocatable :: s(:), hato(:), g(:), y(:)
495
496 push_sub(solve_schroedinger)
497
498 ierr = 0
499
500 ! Allocations...
501 safe_allocate( s(1:psp%g%nrval))
502 safe_allocate(hato(1:psp%g%nrval))
503 safe_allocate( g(1:psp%g%nrval))
504 safe_allocate( y(1:psp%g%nrval))
505 safe_allocate(prev(1:psp%g%nrval, 1))
506 safe_allocate( rho(1:psp%g%nrval, 1))
507 safe_allocate( ve(1:psp%g%nrval, 1))
508 hato = m_zero
509 g = m_zero
510 y = m_zero
511 rho = m_zero
512 ve = m_zero
513
514 ! These numerical parameters have to be fixed for egofv to work.
515 s(2:psp%g%nrval) = psp%g%drdi(2:psp%g%nrval)*psp%g%drdi(2:psp%g%nrval)
516 s(1) = s(2)
517 a2b4 = m_fourth*psp%g%a**2
518
519 ! "Double" self-consistent loop: nonlocal and XC parts have to be calculated
520 ! self-consistently.
521 diff = 1e5_real64
522 iter = 0
523 self_consistent: do while(diff > tol)
524 prev = rho
525 iter = iter + 1
526 do n = 1, psp%conf%p
527 l = psp%conf%l(n)
528 do ir = 2, psp%g%nrval
529 vtot = 2*psp%vlocal(ir) + ve(ir, 1) + real(l*(l + 1), real64)/(psp%g%rofi(ir)**2)
530 nonl = m_zero
531 if (iter>2 .and. psp%l_max >= 0 .and. psp%rphi(ir, n) > 1.0e-7_real64) then
532 do i = 1, 3
533 do j = 1, 3
534 do irr = 2, psp%g%nrval
535 if(psp%kb(irr,l,j) < 1e-100_real64 .or. psp%kb(ir, l, i) < 1e-100_real64) cycle !To avoid FPE
536 nonl = nonl + psp%h(l, i, j)*psp%kb(ir, l, i)* &
537 psp%g%drdi(irr)*psp%g%rofi(irr)*psp%rphi(irr, n)*psp%kb(irr,l,j)
538 end do
539 end do
540 end do
541 nonl = m_two * nonl / psp%rphi(ir, n) * psp%g%rofi(ir)
542 end if
543 vtot = vtot + nonl
544 hato(ir) = vtot*s(ir) + a2b4
545 end do
546 hato(1) = hato(2)
547 ! We will assume there is only the possibility of two equal l numbers...
548 nnode = 1
549 do k = 1, n - 1
550 if (psp%conf%l(k) == psp%conf%l(n)) nnode = 2
551 end do
552 nprin = l + 1
553 if (iter == 1) then
554 e = -((psp%z_val/real(nprin, real64) )**2)
555 z = psp%z_val
556 else
557 e = psp%eigen(n)
558 z = psp%z_val
559 end if
560 dr = -1.0e5_real64
561 rmax = psp%g%rofi(psp%g%nrval)
562 call egofv(namespace, hato, s, psp%g%nrval, e, g, y, l, z, &
563 real(psp%g%a, real64), real(psp%g%b, real64), rmax, nprin, nnode, dr, ierr)
564 if (ierr /= 0) exit self_consistent
565 psp%eigen(n) = e
566
567 psp%rphi(2:psp%g%nrval, n) = g(2:psp%g%nrval) * sqrt(psp%g%drdi(2:psp%g%nrval))
568 psp%rphi(1, n) = psp%rphi(2, n)
569 end do
570 rho = m_zero
571 do n = 1, psp%conf%p
572 rho(1:psp%g%nrval, 1) = rho(1:psp%g%nrval, 1) + psp%conf%occ(n,1)*psp%rphi(1:psp%g%nrval, n)**2
573 end do
574 if (iter>1) rho = m_half*(rho + prev)
575 diff = sqrt(sum(psp%g%drdi(2:psp%g%nrval)*(rho(2:psp%g%nrval, 1)-prev(2:psp%g%nrval, 1))**2))
576 call atomhxc(namespace, 'LDA', psp%g, 1, rho, ve)
578 end do self_consistent
579
580 if (ierr == 0) then
581 ! checking normalization of the calculated wavefunctions
582 !do l = 0, psp%l_max_occ
583 do n = 1, psp%conf%p
584 e = sqrt(sum(psp%g%drdi(2:psp%g%nrval)*psp%rphi(2:psp%g%nrval, n)**2))
585 e = abs(e - m_one)
586 if (e > 1.0e-5_real64) then
587 write(message(1), '(a,i2,a)') "Eigenstate for n = ", n , ' is not normalized'
588 write(message(2), '(a, f12.6,a)') '(abs(1-norm) = ', e, ')'
589 call messages_warning(2, namespace=namespace)
590 end if
591 end do
592
593 ! Output in Ha and not in stupid Rydbergs.
594 psp%eigen = psp%eigen / m_two
595 end if
596
597 ! Deallocations.
598 safe_deallocate_a(s)
599 safe_deallocate_a(hato)
600 safe_deallocate_a(g)
601 safe_deallocate_a(y)
602 safe_deallocate_a(prev)
603 safe_deallocate_a(rho)
604 safe_deallocate_a(ve)
605
606 pop_sub(solve_schroedinger)
607 end subroutine solve_schroedinger
608
609
610 ! ---------------------------------------------------------
611 subroutine hgh_debug(psp, dir, namespace)
612 type(ps_hgh_t), intent(in) :: psp
613 character(len=*), intent(in) :: dir
614 type(namespace_t), intent(in) :: namespace
615
616 integer :: hgh_unit, loc_unit, dat_unit, kbp_unit, wav_unit, i, l, k
617 character(len=256) :: dirname
618
619 push_sub(hgh_debug)
620
621 ! Open files.
622 dirname = trim(dir)//'/hgh.'//trim(psp%atom_name)
623 call io_mkdir(trim(dirname), namespace)
624 hgh_unit = io_open(trim(dirname)//'/hgh', namespace, action='write')
625 loc_unit = io_open(trim(dirname)//'/local', namespace, action='write')
626 dat_unit = io_open(trim(dirname)//'/info', namespace, action='write')
627 kbp_unit = io_open(trim(dirname)//'/nonlocal', namespace, action='write')
628 wav_unit = io_open(trim(dirname)//'/wave', namespace, action='write')
629
630 ! Writes down the input file, to be checked against SHARE_DIR/pseudopotentials/HGH/ATOM_NAME.hgh
631 write(hgh_unit,'(a5,i6,5f12.6)') psp%atom_name, psp%z_val, psp%rlocal, psp%c(1:4)
632 write(hgh_unit,'( 11x,4f12.6)') psp%rc(0), (psp%h(0,i,i), i = 1, 3)
633 do k = 1, 3
634 write(hgh_unit,'( 11x,4f12.6)') psp%rc(k), (psp%h(k, i, i), i = 1, 3)
635 write(hgh_unit,'( 23x,4f12.6)') (psp%k(k, i, i), i = 1, 3)
636 end do
637
638 ! Writes down some info.
639 write(dat_unit,'(a,i3)') 'lmax = ', psp%l_max
640 if (psp%l_max >= 0) then
641 write(dat_unit,'(a,4f14.6)') 'kbr = ', psp%kbr
642 end if
643 write(dat_unit,'(a,5f14.6)') 'eigen = ', psp%eigen
644 write(dat_unit,'(a,5f14.6)') 'occ = ', psp%conf%occ(1:psp%conf%p, 1)
645 ! Writes down local part.
646 do i = 1, psp%g%nrval
647 write(loc_unit, *) psp%g%rofi(i), psp%vlocal(i)
648 end do
649
650 ! Writes down nonlocal part.
651 if (psp%l_max >= 0) then
652 do i = 1, psp%g%nrval
653 write(kbp_unit, '(10es14.4)') psp%g%rofi(i), ( (psp%kb(i, l, k) ,k = 1, 3),l = 0, psp%l_max)
654 end do
655 end if
656
657 ! And the pseudo-wavefunctions.
658 do i = 1, psp%g%nrval
659 write(wav_unit, *) psp%g%rofi(i), (psp%rphi(i, l), l = 1, psp%conf%p)
660 end do
661
662 ! Closes files and exits
663 call io_close(hgh_unit)
664 call io_close(loc_unit)
665 call io_close(wav_unit)
666 call io_close(dat_unit)
667 call io_close(kbp_unit)
668
669 pop_sub(hgh_debug)
670 end subroutine hgh_debug
671
672end module ps_hgh_oct_m
673
674!! Local Variables:
675!! mode: f90
676!! coding: utf-8
677!! End:
Define which routines can be seen from the outside.
Definition: loct_math.F90:149
double exp(double __x) __attribute__((__nothrow__
double sqrt(double __x) __attribute__((__nothrow__
subroutine, public atomhxc(namespace, functl, g, nspin, dens, v, extra)
Definition: atomic.F90:253
subroutine, public egofv(namespace, h, s, n, e, g, y, l, z, a, b, rmax, nprin, nnode, dr, ierr)
egofv determines the eigenenergy and wavefunction corresponding ! to a particular l,...
Definition: atomic.F90:765
real(real64), parameter, public m_two
Definition: global.F90:189
real(real64), parameter, public m_max_exp_arg
Definition: global.F90:207
real(real64), parameter, public m_zero
Definition: global.F90:187
real(real64), parameter, public m_pi
some mathematical constants
Definition: global.F90:185
real(real64), parameter, public m_fourth
Definition: global.F90:196
real(real64), parameter, public m_min_exp_arg
Definition: global.F90:206
real(real64), parameter, public m_epsilon
Definition: global.F90:203
real(real64), parameter, public m_half
Definition: global.F90:193
real(real64), parameter, public m_one
Definition: global.F90:188
real(real64), parameter, public m_three
Definition: global.F90:190
real(real64), parameter, public m_five
Definition: global.F90:192
Definition: io.F90:114
subroutine, public io_close(iunit, grp)
Definition: io.F90:468
subroutine, public io_mkdir(fname, namespace, parents)
Definition: io.F90:354
integer function, public io_open(file, namespace, action, status, form, position, die, recl, grp)
Definition: io.F90:395
subroutine, public logrid_find_parameters(namespace, zz, aa, bb, np)
Definition: logrid.F90:309
integer, parameter, public logrid_psf
log grid used in Troullier-Martins code
Definition: logrid.F90:135
subroutine, public logrid_end(grid)
Definition: logrid.F90:213
subroutine, public logrid_init(grid, flavor, aa, bb, nrval)
Definition: logrid.F90:156
subroutine, public messages_warning(no_lines, all_nodes, namespace)
Definition: messages.F90:543
character(len=256), dimension(max_lines), public message
to be output by fatal, warning
Definition: messages.F90:160
subroutine, public messages_fatal(no_lines, only_root_writes, namespace)
Definition: messages.F90:420
subroutine, public hgh_end(psp)
Definition: ps_hgh.F90:228
subroutine solve_schroedinger(psp, ierr, namespace)
Definition: ps_hgh.F90:578
subroutine projectorr_scalar(r, np, p, i, l, proj)
Definition: ps_hgh.F90:540
subroutine, public hgh_debug(psp, dir, namespace)
Definition: ps_hgh.F90:705
integer function load_params(unit, params, namespace)
Definition: ps_hgh.F90:305
subroutine, public hgh_get_eigen(psp, eigen)
Definition: ps_hgh.F90:289
subroutine, public hgh_process(psp, namespace)
Definition: ps_hgh.F90:247
subroutine, public hgh_init(psp, filename, namespace)
Definition: ps_hgh.F90:183
subroutine get_cutoff_radii(psp)
Definition: ps_hgh.F90:475
subroutine vlocalr_scalar(r, np, p, vloc)
Definition: ps_hgh.F90:503
The following data type contains: (a) the pseudopotential parameters, as read from a *....
Definition: ps_hgh.F90:144