Octopus
jellium.F90
Go to the documentation of this file.
1!! Copyright (C) 2002-2006 M. Marques, A. Castro, A. Rubio, G. Bertsch
2!! Copyright (C) 2023-2024 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#include "global.h"
20
21module jellium_oct_m
22 use debug_oct_m
23 use global_oct_m
24 use io_oct_m
26 use mpi_oct_m
28 use parser_oct_m
31 use unit_oct_m
33
34 implicit none
35
36 private
37 public :: &
38 jellium_t, &
45
46 integer, public, parameter :: &
47 SPECIES_JELLIUM = 3, & !< jellium sphere.
50 species_usdef = 123, &
53
54 type, abstract, extends(species_t) :: jellium_t
55 private
56
57 real(real64) :: omega
58
59 contains
60 procedure :: iwf_fix_qn => jellium_iwf_fix_qn
61 procedure :: get_iwf_radius => jellium_get_iwf_radius
62 procedure :: is_local => jellium_is_local
63 procedure :: init_potential => jellium_init_potential
64 procedure :: debug => jellium_debug
65 procedure :: build => jellium_build
66 procedure :: get_omega => jellium_get_omega
67 procedure :: is_user_defined => jellium_user_defined
68 end type jellium_t
69
70 type, extends(jellium_t) :: jellium_sphere_t
71 private
72
73 real(real64) :: jradius
74
75 contains
76 procedure :: radius => jellium_radius
77 procedure :: set_radius => jellium_set_radius
79 end type jellium_sphere_t
80
81 type, extends(jellium_t) :: jellium_slab_t
82 private
83
84 real(real64) :: jthick
85
86 contains
87 procedure :: thickness => jellium_thick
88 procedure :: set_thickness => jellium_set_thickness
89 procedure :: get_density => jellium_slab_density
91 end type jellium_slab_t
92
93 type, extends(jellium_t) :: jellium_charge_t
94 private
95
96 character(len=200), public :: density_formula
97
98 contains
99 procedure :: rho_string => jellium_rho_string
101 end type jellium_charge_t
102
103 type, extends (jellium_t) :: species_from_file_t
104 private
105
106 contains
108 end type species_from_file_t
109
110 type, extends (jellium_t) :: species_user_defined_t
111 private
112
113 character(len=1024), public :: potential_formula
114 contains
115 procedure :: user_pot => jellium_userdef_pot
118
119 type, extends (jellium_t) :: species_charge_density_t
120 private
121
122 character(len=200), public :: density_formula
123 contains
124 procedure :: rho_string => species_rho_string
127
128 interface jellium_sphere_t
129 procedure jellium_sphere_constructor
130 end interface jellium_sphere_t
131
132 interface jellium_slab_t
133 procedure jellium_slab_constructor
134 end interface jellium_slab_t
135
136 interface jellium_charge_t
137 procedure jellium_charge_constructor
138 end interface jellium_charge_t
140 interface species_from_file_t
142 end interface species_from_file_t
143
144 interface species_user_defined_t
146 end interface species_user_defined_t
149 procedure species_charge_density_constructor
151
152
153contains
156 ! ---------------------------------------------------------
157 function jellium_slab_constructor(label, index) result(spec)
158 class(jellium_slab_t), pointer :: spec
159 character(len=*), intent(in) :: label
160 integer, intent(in) :: index
161
164 safe_allocate(spec)
165
166 call species_init(spec, label, index)
167
168 spec%omega = m_zero
169 spec%jthick = -m_one
172 end function jellium_slab_constructor
173
174 ! ---------------------------------------------------------
175 subroutine jellium_slab_finalize(this)
176 type(jellium_slab_t), intent(inout) :: this
178 push_sub(jellium_slab_finalize)
179
180 call species_end(this)
184
185 ! ---------------------------------------------------------
186 function jellium_sphere_constructor(label, index) result(spec)
187 class(jellium_sphere_t), pointer :: spec
188 character(len=*), intent(in) :: label
189 integer, intent(in) :: index
190
193 safe_allocate(spec)
194
195 call species_init(spec, label, index)
197 spec%omega = m_zero
198 spec%jradius = m_half
199
201 end function jellium_sphere_constructor
202
204 ! ---------------------------------------------------------
205 subroutine jellium_sphere_finalize(this)
206 type(jellium_sphere_t), intent(inout) :: this
207
210 call species_end(this)
211
213 end subroutine jellium_sphere_finalize
214
215 ! ---------------------------------------------------------
216 function jellium_charge_constructor(label, index) result(spec)
217 class(jellium_charge_t), pointer :: spec
218 character(len=*), intent(in) :: label
219 integer, intent(in) :: index
220
222
223 safe_allocate(spec)
224
225 call species_init(spec, label, index)
226
227 spec%omega = m_zero
228 spec%density_formula = ""
229
231 end function jellium_charge_constructor
232
233
234 ! ---------------------------------------------------------
235 subroutine jellium_charge_finalize(this)
236 type(jellium_charge_t), intent(inout) :: this
237
239
240 call species_end(this)
241
243 end subroutine jellium_charge_finalize
244
245
246 ! ---------------------------------------------------------
247 function species_from_file_constructor(label, index) result(spec)
248 class(species_from_file_t), pointer :: spec
249 character(len=*), intent(in) :: label
250 integer, intent(in) :: index
251
253
254 safe_allocate(spec)
255
256 call species_init(spec, label, index)
257
258 spec%omega = m_zero
259
262
263 ! ---------------------------------------------------------
264 subroutine species_from_file_finalize(this)
265 type(species_from_file_t), intent(inout) :: this
266
269 call species_end(this)
270
272 end subroutine species_from_file_finalize
273
274
275 ! ---------------------------------------------------------
276 function species_user_defined_constructor(label, index) result(spec)
277 class(species_user_defined_t), pointer :: spec
278 character(len=*), intent(in) :: label
279 integer, intent(in) :: index
280
282
283 safe_allocate(spec)
284
285 call species_init(spec, label, index)
286
287 spec%potential_formula = ""
288 spec%omega = m_zero
289
292
293
294 ! ---------------------------------------------------------
295 subroutine species_user_defined_finalize(this)
296 type(species_user_defined_t), intent(inout) :: this
297
299
300 call species_end(this)
301
303 end subroutine species_user_defined_finalize
304
305
306 ! ---------------------------------------------------------
307 function species_charge_density_constructor(label, index) result(spec)
308 class(species_charge_density_t), pointer :: spec
309 character(len=*), intent(in) :: label
310 integer, intent(in) :: index
311
313
314 safe_allocate(spec)
315
316 call species_init(spec, label, index)
317
318 spec%omega = m_zero
319 spec%density_formula = ""
320
323
324
325 ! ---------------------------------------------------------
326 subroutine species_charge_density_finalize(this)
327 type(species_charge_density_t), intent(inout) :: this
330
331 call species_end(this)
332
335
336 ! ---------------------------------------------------------
337 real(real64) pure function jellium_get_omega(spec)
338 class(jellium_t), intent(in) :: spec
339 jellium_get_omega = spec%omega
340 end function jellium_get_omega
341
342
343 ! ---------------------------------------------------------
344 real(real64) pure function jellium_radius(spec)
345 class(jellium_sphere_t), intent(in) :: spec
346 jellium_radius = spec%jradius
347 end function jellium_radius
348
349 ! ---------------------------------------------------------
350 pure subroutine jellium_set_radius(spec, radius)
351 class(jellium_sphere_t), intent(inout) :: spec
352 real(real64), intent(in) :: radius
353 spec%jradius = radius
354 end subroutine jellium_set_radius
355
356 ! ---------------------------------------------------------
357 real(real64) pure function jellium_thick(spec)
358 class(jellium_slab_t), intent(in) :: spec
359 jellium_thick = spec%jthick
360 end function jellium_thick
361
362 ! ---------------------------------------------------------
363 pure subroutine jellium_set_thickness(spec, thick)
364 class(jellium_slab_t), intent(inout) :: spec
365 real(real64), intent(in) :: thick
366 spec%jthick = thick
367 end subroutine jellium_set_thickness
368
369 ! ---------------------------------------------------------
370 character(len=200) pure function jellium_rho_string(spec)
371 class(jellium_charge_t), intent(in) :: spec
372 jellium_rho_string = trim(spec%density_formula)
373 end function jellium_rho_string
374
375 ! ---------------------------------------------------------
376 character(len=200) pure function species_rho_string(spec)
377 class(species_charge_density_t), intent(in) :: spec
378 species_rho_string = trim(spec%density_formula)
379 end function species_rho_string
380
381
382 ! ---------------------------------------------------------
383 complex(real64) function jellium_userdef_pot(spec, dim, xx, r)
384 class(species_user_defined_t), intent(in) :: spec
385 integer, intent(in) :: dim
386 real(real64), intent(in) :: xx(:)
387 real(real64), intent(in) :: r
389 real(real64) :: pot_re, pot_im
390
391 push_sub(jellium_userdef_pot)
392
393 call parse_expression(pot_re, pot_im, dim, xx, r, m_zero, spec%potential_formula)
394 jellium_userdef_pot = pot_re + m_zi * pot_im
395
396 pop_sub(jellium_userdef_pot)
397 end function jellium_userdef_pot
398
399 ! ---------------------------------------------------------
401 subroutine jellium_iwf_fix_qn(spec, namespace, nspin, dim)
402 class(jellium_t), intent(inout) :: spec
403 type(namespace_t), intent(in) :: namespace
404 integer, intent(in) :: nspin
405 integer, intent(in) :: dim
406
407 integer :: is, i, n1, n2, n3
408
409 push_sub(jellium_iwf_fix_qn)
410
411 select case (dim)
412 case (1)
413 do is = 1, nspin
414 do i = 1, spec%niwfs
415 spec%iwf_i(i, is) = i
416 spec%iwf_n(i, is) = 0
417 spec%iwf_l(i, is) = 0
418 spec%iwf_m(i, is) = 0
419 spec%iwf_j(i) = m_zero
420 end do
421 end do
422
423 case (2)
424 do is = 1, nspin
425 i = 1
426 n1 = 1
427 n2 = 1
428 do
429 spec%iwf_i(i, is) = n1
430 spec%iwf_n(i, is) = 1
431 spec%iwf_l(i, is) = n2
432 spec%iwf_m(i, is) = 0
433 spec%iwf_j(i) = m_zero
434 i = i + 1
435 if (i>spec%niwfs) exit
436
437 spec%iwf_i(i, is) = n1+1
438 spec%iwf_n(i, is) = 1
439 spec%iwf_l(i, is) = n2
440 spec%iwf_m(i, is) = 0
441 spec%iwf_j(i) = m_zero
442 i = i + 1
443 if (i>spec%niwfs) exit
444
445 spec%iwf_i(i, is) = n1
446 spec%iwf_n(i, is) = 1
447 spec%iwf_l(i, is) = n2+1
448 spec%iwf_m(i, is) = 0
449 spec%iwf_j(i) = m_zero
450 i = i + 1
451 if (i>spec%niwfs) exit
452
453 n1 = n1 + 1; n2 = n2 + 1
454 end do
455 end do
457 case (3)
458 do is = 1, nspin
459 i = 1
460 n1 = 1
461 n2 = 1
462 n3 = 1
463 do
464 spec%iwf_i(i, is) = n1
465 spec%iwf_n(i, is) = 1
466 spec%iwf_l(i, is) = n2
467 spec%iwf_m(i, is) = n3
468 spec%iwf_j(i) = m_zero
469 i = i + 1
470 if (i>spec%niwfs) exit
471
472 spec%iwf_i(i, is) = n1+1
473 spec%iwf_n(i, is) = 1
474 spec%iwf_l(i, is) = n2
475 spec%iwf_m(i, is) = n3
476 spec%iwf_j(i) = m_zero
477 i = i + 1
478 if (i>spec%niwfs) exit
479
480 spec%iwf_i(i, is) = n1
481 spec%iwf_n(i, is) = 1
482 spec%iwf_l(i, is) = n2+1
483 spec%iwf_m(i, is) = 0
484 spec%iwf_j(i) = m_zero
485 i = i + 1
486 if (i>spec%niwfs) exit
487
488 spec%iwf_i(i, is) = n1
489 spec%iwf_n(i, is) = 1
490 spec%iwf_l(i, is) = n2
491 spec%iwf_m(i, is) = n3+1
492 spec%iwf_j(i) = m_zero
493 i = i + 1
494 if (i>spec%niwfs) exit
495
496 spec%iwf_i(i, is) = n1+1
497 spec%iwf_n(i, is) = 1
498 spec%iwf_l(i, is) = n2+1
499 spec%iwf_m(i, is) = n3
500 spec%iwf_j(i) = m_zero
501 i = i + 1
502 if (i>spec%niwfs) exit
503
504 spec%iwf_i(i, is) = n1+1
505 spec%iwf_n(i, is) = 1
506 spec%iwf_l(i, is) = n2
507 spec%iwf_m(i, is) = n3+1
508 spec%iwf_j(i) = m_zero
509 i = i + 1
510 if (i>spec%niwfs) exit
511
512 spec%iwf_i(i, is) = n1
513 spec%iwf_n(i, is) = 1
514 spec%iwf_l(i, is) = n2+1
515 spec%iwf_m(i, is) = n3+1
516 spec%iwf_j(i) = m_zero
517 i = i + 1
518 if (i>spec%niwfs) exit
519
520 n1 = n1 + 1
521 n2 = n2 + 1
522 n3 = n3 + 1
523 end do
524 end do
525 case default
526 ! Not doing anything to allow for N-D simulations
527 end select
528
529 pop_sub(jellium_iwf_fix_qn)
530 end subroutine jellium_iwf_fix_qn
531
532 ! ---------------------------------------------------------
534 real(real64) pure function jellium_get_iwf_radius(spec, ii, is, threshold) result(radius)
535 class(jellium_t), intent(in) :: spec
536 integer, intent(in) :: ii
537 integer, intent(in) :: is
538 real(real64), optional, intent(in) :: threshold
539
540 real(real64) threshold_
541
542 threshold_ = optional_default(threshold, 0.001_real64)
543
544 radius = sqrt(-m_two*log(threshold_)/spec%omega)
545
546 ! The values for hydrogenic and harmonic-oscillator wavefunctions
547 ! come from taking the exponential part (i.e. the one that controls
548 ! the asymptotic behavior at large r), and setting it equal to
549 ! the threshold.
550 end function jellium_get_iwf_radius
551
552 ! ---------------------------------------------------------
553 logical pure function jellium_is_local(spec) result(is_local)
554 class(jellium_t), intent(in) :: spec
555
556 is_local = .true.
557 end function jellium_is_local
558
559 ! ---------------------------------------------------------
561 ! ---------------------------------------------------------
562 subroutine jellium_init_potential(this, namespace, grid_cutoff, filter)
563 class(jellium_t), intent(inout) :: this
564 type(namespace_t), intent(in) :: namespace
565 real(real64), intent(in) :: grid_cutoff
566 integer, intent(in) :: filter
567
568 push_sub(jellium_init_potential)
569
570
572 end subroutine jellium_init_potential
573
574 ! ---------------------------------------------------------
575 subroutine jellium_debug(spec, dir, namespace, gmax)
576 class(jellium_t), intent(in) :: spec
577 character(len=*), intent(in) :: dir
578 type(namespace_t), intent(in) :: namespace
579 real(real64), intent(in) :: gmax
580
581 character(len=256) :: dirname
582 integer :: iunit
583
584 if (.not. mpi_grp_is_root(mpi_world)) then
585 return
586 end if
587
588 push_sub(jellium_debug)
589
590 dirname = trim(dir)//'/'//trim(spec%get_label())
591
592 call io_mkdir(dirname, namespace)
593
594 iunit = io_open(trim(dirname)//'/info', namespace, action='write')
595
596 write(iunit, '(a,i3)') 'Index = ', spec%get_index()
597 write(iunit, '(2a)') 'Label = ', trim(spec%get_label())
598 write(iunit, '(a,f15.2)') 'z_val = ', spec%get_zval()
599 write(iunit, '(a,f15.2)') 'mass = ', spec%get_mass()
600 write(iunit, '(a,f15.2)') 'vdw_radius = ', spec%get_vdw_radius()
601 write(iunit, '(a,l1)') 'local = ', spec%is_local()
602
603 select type(spec)
604 type is(species_from_file_t)
605 write(iunit, '(a,f15.2)') 'z = ', spec%get_z()
606 write(iunit,'(a)') 'Species read from file "'//trim(spec%get_filename())//'".'
607 type is(jellium_sphere_t)
608 write(iunit, '(a,f15.2)') 'z = ', spec%get_z()
609 write(iunit, '(a,f15.2)') 'jradius= ', spec%radius()
610 type is(jellium_slab_t)
611 write(iunit, '(a,f15.2)') 'z = ', spec%get_z()
612 write(iunit, '(a,f15.2)') 'jthick= ', spec%thickness()
614 write(iunit, '(2a)') 'usdef = ', trim(spec%potential_formula)
615 end select
616
617 write(iunit, '(a,i3)') 'hubbard_l = ', spec%get_hubbard_l()
618 write(iunit, '(a,f15.2)') 'hubbard_U = ', spec%get_hubbard_U()
619 write(iunit, '(a,f15.2)') 'hubbard_j = ', spec%get_hubbard_j()
620 write(iunit, '(a,f15.2)') 'hubbard_alpha = ', spec%get_hubbard_alpha()
621
622 call io_close(iunit)
623 pop_sub(jellium_debug)
624 end subroutine jellium_debug
625
626 ! ---------------------------------------------------------
627 subroutine jellium_build(spec, namespace, ispin, dim, print_info)
628 class(jellium_t), intent(inout) :: spec
629 type(namespace_t), intent(in) :: namespace
630 integer, intent(in) :: ispin
631 integer, intent(in) :: dim
632 logical, optional, intent(in) :: print_info
633
634 logical :: print_info_
635 integer :: i
636 real(real64) :: pot_re, pot_im, xx(dim), rr
637
638 push_sub(jellium_build)
639
640 print_info_ = optional_default(print_info, .true.)
641
642 ! masses are always in amu, so convert them to a.u.
643 call spec%set_mass(units_to_atomic(unit_amu, spec%get_mass()))
644
645 spec%has_density = .false.
647 select type (spec)
649 if (print_info_) then
650 write(message(1),'(a,a,a)') 'Species "',trim(spec%get_label()),'" is a user-defined potential.'
651 i = min(237, len_trim(spec%potential_formula)-1) ! I subtract 1 to avoid the non-printable C "end-of-string" character.
652 write(message(2),'(a,a)') ' Potential = ', trim(spec%potential_formula(1:i))
653 if (len(trim(spec%potential_formula)) > 237) then
654 message(2) = trim(message(2))//'...'
655 end if
656 call messages_info(2, namespace=namespace)
657 end if
658 spec%niwfs = int(max(2*spec%get_zval(), m_one))
659
660 xx = m_zero
661 xx(1) = 0.01_real64
662 rr = norm2(xx)
663 call parse_expression(pot_re, pot_im, dim, xx, rr, m_zero, spec%potential_formula)
664 spec%omega = sqrt(abs(m_two / 1.0e-4_real64 * pot_re)) ! why...?
665 ! To avoid problems with constant potentials.
666 if (spec%omega <= m_zero) spec%omega = 0.1_real64
667
669 if (print_info_) then
670 write(message(1),'(a)') 'Species read from file "'//trim(spec%get_filename())//'".'
671 call messages_info(1, namespace=namespace)
672 end if
673 spec%niwfs = 2*nint(spec%get_zval()+m_half)
674 spec%omega = 0.1_real64
675
676 type is(jellium_sphere_t)
677 if (print_info_) then
678 write(message(1),'(a,a,a)') 'Species "', trim(spec%get_label()), &
679 '" is a jellium sphere / approximated point particle.'
680 write(message(2),'(a,f11.6)') ' Valence charge = ', spec%get_zval()
681 write(message(3),'(a,f11.6)') ' Radius [a.u] = ', spec%jradius
682 write(message(4),'(a,f11.6)') ' Rs [a.u] = ', spec%jradius * spec%get_zval() ** (-m_one/m_three)
683 call messages_info(4, namespace=namespace)
684 end if
685 spec%niwfs = species_closed_shell_size(2*nint(spec%get_zval()+m_half))
686 spec%omega = 0.1_real64
687
688 type is(jellium_slab_t)
689 if (print_info_) then
690 write(message(1),'(a,a,a)') 'Species "',trim(spec%get_label()),'" is a jellium slab.'
691 write(message(2),'(a,f11.6)') ' Valence charge = ', spec%get_zval()
692 write(message(3),'(a,f11.6)') ' Thickness [a.u] = ', spec%jthick
693 !write(message(4),'(a,f11.6)') ' Rs [a.u] = ', ( M_THREE /( M_FOUR *M_PI ) &
694 !& *spec%get_zval() /( *sb%lsize(1) *sb%lsize(2) ) )**(1.0/3.0)
695 call messages_info(3, namespace=namespace)
696 end if
697 spec%niwfs = 2*nint(spec%get_zval()+m_half)
698 spec%omega = 0.1_real64
699
700 type is(jellium_charge_t)
701 spec%niwfs = int(max(2*spec%get_zval(), m_one))
702 spec%omega = spec%get_zval()
703 spec%has_density = .true.
704 if (print_info_) then
705 write(message(1),'(a,a,a)') 'Species "', trim(spec%get_label()), '" is a distribution of charge:'
706 write(message(2),'(a,a,a)') ' rho is enclosed in volume defined by the "', &
707 trim(spec%density_formula), '" block'
708 write(message(3),'(a,f11.6)') ' Z = ', spec%get_zval()
709 call messages_info(3, namespace=namespace)
710 end if
711
713 spec%niwfs = int(max(2*spec%get_zval(), m_one))
714 spec%omega = spec%get_zval()
715 spec%has_density = .true.
716 if (print_info_) then
717 write(message(1),'(a,a,a)') 'Species "', trim(spec%get_label()), '" is a distribution of charge:'
718 write(message(2),'(a,a)') ' rho = ', trim(spec%density_formula)
719 write(message(3),'(a,f11.6)') ' Z = ', spec%get_zval()
720 call messages_info(3, namespace=namespace)
721 end if
722 class default
723 call messages_input_error(namespace, 'Species', 'Unknown species type')
724 end select
725
726 ! since there is no real cap, make sure there are at least a few available
727 spec%niwfs = max(5, spec%niwfs)
728
729 safe_allocate(spec%iwf_n(1:spec%niwfs, 1:ispin))
730 safe_allocate(spec%iwf_l(1:spec%niwfs, 1:ispin))
731 safe_allocate(spec%iwf_m(1:spec%niwfs, 1:ispin))
732 safe_allocate(spec%iwf_i(1:spec%niwfs, 1:ispin))
733 safe_allocate(spec%iwf_j(1:spec%niwfs))
734
735 call spec%iwf_fix_qn(namespace, ispin, dim)
736
737 write(message(1),'(a,i6,a,i6)') 'Number of orbitals: ', spec%niwfs
738 if (print_info_) call messages_info(1, namespace=namespace)
739
740 pop_sub(jellium_build)
741 end subroutine jellium_build
742
743 ! ---------------------------------------------------------
745 logical pure function jellium_user_defined(spec)
746 class(jellium_t), intent(in) :: spec
747
748 select type(spec)
749 class is(species_user_defined_t)
753 class is(species_from_file_t)
755 class default
756 jellium_user_defined = .false.
757 end select
758
759 end function jellium_user_defined
760
761 ! ---------------------------------------------------------
763 real(real64) pure function jellium_slab_density(slab, box_dim) result(density)
764 class(jellium_slab_t), intent(in) :: slab
765 real(real64), intent(in) :: box_dim(:)
766
767 ! Note the factor of 4 as box_dim is half of the box size
768 density = slab%get_zval() / (box_dim(1) * box_dim(2) * m_four * slab%jthick)
769
770 end function jellium_slab_density
771end module jellium_oct_m
772
773!! Local Variables:
774!! mode: f90
775!! coding: utf-8
776!! End:
double log(double __x) __attribute__((__nothrow__
double sqrt(double __x) __attribute__((__nothrow__
real(real64), parameter, public m_zero
Definition: global.F90:187
real(real64), parameter, public m_half
Definition: global.F90:193
real(real64), parameter, public m_one
Definition: global.F90:188
Definition: io.F90:114
subroutine species_user_defined_finalize(this)
Definition: jellium.F90:389
real(real64) pure function jellium_get_omega(spec)
Definition: jellium.F90:431
real(real64) pure function jellium_radius(spec)
Definition: jellium.F90:438
logical pure function jellium_user_defined(spec)
Is the species user-defined or not.
Definition: jellium.F90:839
logical pure function jellium_is_local(spec)
Definition: jellium.F90:647
pure subroutine jellium_set_thickness(spec, thick)
Definition: jellium.F90:457
subroutine jellium_iwf_fix_qn(spec, namespace, nspin, dim)
set up quantum numbers of orbitals
Definition: jellium.F90:495
integer, parameter, public species_charge_density
user-defined function for charge density
Definition: jellium.F90:139
integer, parameter, public species_jellium_charge_density
jellium volume read from file
Definition: jellium.F90:139
subroutine jellium_charge_finalize(this)
Definition: jellium.F90:329
class(jellium_slab_t) function, pointer jellium_slab_constructor(label, index)
Definition: jellium.F90:251
class(species_user_defined_t) function, pointer species_user_defined_constructor(label, index)
Definition: jellium.F90:370
subroutine jellium_slab_finalize(this)
Definition: jellium.F90:269
subroutine jellium_build(spec, namespace, ispin, dim, print_info)
Definition: jellium.F90:721
real(real64) pure function jellium_get_iwf_radius(spec, ii, is, threshold)
Return radius outside which orbital is less than threshold value 0.001.
Definition: jellium.F90:628
class(jellium_charge_t) function, pointer jellium_charge_constructor(label, index)
Definition: jellium.F90:310
class(jellium_sphere_t) function, pointer jellium_sphere_constructor(label, index)
Definition: jellium.F90:280
pure subroutine jellium_set_radius(spec, radius)
Definition: jellium.F90:444
subroutine species_charge_density_finalize(this)
Definition: jellium.F90:420
character(len=200) pure function jellium_rho_string(spec)
Definition: jellium.F90:464
subroutine species_from_file_finalize(this)
Definition: jellium.F90:358
real(real64) pure function jellium_thick(spec)
Definition: jellium.F90:451
real(real64) pure function jellium_slab_density(slab, box_dim)
Returns the electron density of a jellium slab.
Definition: jellium.F90:857
complex(real64) function jellium_userdef_pot(spec, dim, xx, r)
Definition: jellium.F90:477
integer, parameter, public species_from_file
Definition: jellium.F90:139
class(species_from_file_t) function, pointer species_from_file_constructor(label, index)
Definition: jellium.F90:341
integer, parameter, public species_usdef
user-defined function for local potential
Definition: jellium.F90:139
subroutine jellium_sphere_finalize(this)
Definition: jellium.F90:299
class(species_charge_density_t) function, pointer species_charge_density_constructor(label, index)
Definition: jellium.F90:401
integer, parameter, public species_jellium_slab
jellium slab.
Definition: jellium.F90:139
subroutine jellium_init_potential(this, namespace, grid_cutoff, filter)
Some operations like filtering of the potentials.
Definition: jellium.F90:656
character(len=200) pure function species_rho_string(spec)
Definition: jellium.F90:470
subroutine jellium_debug(spec, dir, namespace, gmax)
Definition: jellium.F90:669
subroutine, public species_end(species)
Definition: species.F90:498
subroutine, public species_init(this, label, index)
Initializes a species object. This should be the first routine to be called (before species_read and ...
Definition: species.F90:287
brief This module defines the class unit_t which is used by the unit_systems_oct_m module.
Definition: unit.F90:132
This module defines the unit system, used for input and output.
An abstract class for species. Derived classes include jellium, all electron, and pseudopotential spe...
Definition: species.F90:143
int true(void)