1 | module m_pseudo_types |
---|
2 | ! |
---|
3 | ! Data structures for a prototype pseudopotential |
---|
4 | ! |
---|
5 | integer, parameter, private :: MAXN_POTS = 8 |
---|
6 | integer, parameter, private :: dp = selected_real_kind(14) |
---|
7 | ! |
---|
8 | public :: dump_pseudo |
---|
9 | ! |
---|
10 | !----------------------------------------------------------- |
---|
11 | type, public :: grid_t |
---|
12 | ! |
---|
13 | ! It should be possible to represent both log and linear |
---|
14 | ! grids with a few parameters here. |
---|
15 | ! |
---|
16 | character(len=20) :: type |
---|
17 | real(kind=dp) :: scale |
---|
18 | real(kind=dp) :: step |
---|
19 | integer :: npts |
---|
20 | end type grid_t |
---|
21 | ! |
---|
22 | type, public :: radfunc_t |
---|
23 | type(grid_t) :: grid |
---|
24 | real(kind=dp), dimension(:), pointer :: data |
---|
25 | end type radfunc_t |
---|
26 | |
---|
27 | type, public :: vps_t |
---|
28 | integer :: l |
---|
29 | integer :: n |
---|
30 | integer :: spin |
---|
31 | real(kind=dp) :: occupation |
---|
32 | real(kind=dp) :: cutoff |
---|
33 | type(radfunc_t) :: V |
---|
34 | end type vps_t |
---|
35 | |
---|
36 | type, public :: header_t |
---|
37 | character(len=2) :: symbol |
---|
38 | real(kind=dp) :: zval |
---|
39 | character(len=10) :: creator |
---|
40 | character(len=10) :: date |
---|
41 | character(len=40) :: flavor |
---|
42 | logical :: relativistic |
---|
43 | logical :: polarized |
---|
44 | character(len=2) :: correlation |
---|
45 | character(len=4) :: core_corrections |
---|
46 | end type header_t |
---|
47 | |
---|
48 | type, public :: pseudo_t |
---|
49 | type(header_t) :: header |
---|
50 | integer :: npots |
---|
51 | integer :: npots_down |
---|
52 | integer :: npots_up |
---|
53 | type(vps_t), dimension(MAXN_POTS) :: pot |
---|
54 | type(radfunc_t) :: core_charge |
---|
55 | type(radfunc_t) :: valence_charge |
---|
56 | end type pseudo_t |
---|
57 | |
---|
58 | |
---|
59 | CONTAINS !=============================================== |
---|
60 | |
---|
61 | subroutine dump_pseudo(pseudo) |
---|
62 | type(pseudo_t), intent(in), target :: pseudo |
---|
63 | |
---|
64 | integer :: i |
---|
65 | type(vps_t), pointer :: pp |
---|
66 | type(radfunc_t), pointer :: rp |
---|
67 | |
---|
68 | print *, "---PSEUDO data:" |
---|
69 | |
---|
70 | do i = 1, pseudo%npots |
---|
71 | pp => pseudo%pot(i) |
---|
72 | rp => pseudo%pot(i)%V |
---|
73 | print *, "VPS ", i, " angular momentum: ", pp%l |
---|
74 | print *, " n: ", pp%n |
---|
75 | print *, " occupation: ", pp%occupation |
---|
76 | print *, " cutoff: ", pp%cutoff |
---|
77 | print *, " spin: ", pp%spin |
---|
78 | print *, "grid data: ", rp%grid%npts, rp%grid%scale |
---|
79 | enddo |
---|
80 | rp => pseudo%valence_charge |
---|
81 | print *, "grid data: ", rp%grid%npts, rp%grid%scale |
---|
82 | rp => pseudo%core_charge |
---|
83 | print *, "grid data: ", rp%grid%npts, rp%grid%scale |
---|
84 | |
---|
85 | end subroutine dump_pseudo |
---|
86 | |
---|
87 | end module m_pseudo_types |
---|
88 | |
---|
89 | |
---|
90 | |
---|
91 | |
---|
92 | |
---|
93 | |
---|
94 | |
---|
95 | |
---|
96 | |
---|
97 | |
---|
98 | |
---|
99 | |
---|
100 | |
---|
101 | |
---|
102 | |
---|
103 | |
---|
104 | |
---|
105 | |
---|
106 | |
---|
107 | |
---|