Octopus
ps_psf_file.F90
Go to the documentation of this file.
1!! Copyright (C) 2002-2006 M. Marques, A. Castro, A. Rubio, G. Bertsch
2!!
3!! This program is free software; you can redistribute it and/or modify
4!! it under the terms of the GNU General Public License as published by
5!! the Free Software Foundation; either version 2, or (at your option)
6!! any later version.
7!!
8!! This program is distributed in the hope that it will be useful,
9!! but WITHOUT ANY WARRANTY; without even the implied warranty of
10!! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
11!! GNU General Public License for more details.
12!!
13!! You should have received a copy of the GNU General Public License
14!! along with this program; if not, write to the Free Software
15!! Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
16!! 02110-1301, USA.
17!!
18
19#include "global.h"
20
22 use debug_oct_m
23 use global_oct_m
28
29 implicit none
30
31 private
32
33 public :: &
37
38 ! First, the contents of the file.
39 type ps_psf_file_t
40 ! Components are public by default
41 character(len=2) :: namatm
42 character(len=2) :: icorr
43 character(len=3) :: irel
44 character(len=4) :: icore
45 character(len=10), private :: method(6)
46 character(len=70) :: title
47
48 integer :: npotd ! l = 0 .. npotd-1
49 integer :: npotu ! l = 1 .. npotu
50 integer :: nr
51 real(real64) :: a, b
52 real(real64) :: zval ! valence charge
53
54 real(real64), allocatable, private :: rofi(:)
55 real(real64), allocatable :: vps(:,:)
56 real(real64), allocatable :: chcore(:)
57 real(real64), allocatable :: rho_val(:)
58 real(real64), allocatable :: vso(:,:)
59 end type ps_psf_file_t
60
61contains
62
63 ! ---------------------------------------------------------
64 subroutine ps_psf_file_read(unit, ascii, psf, namespace)
65 integer, intent(in) :: unit
66 logical, intent(in) :: ascii
67 type(ps_psf_file_t), intent(inout) :: psf
68 type(namespace_t), intent(in) :: namespace
69
70 integer :: ndown, nup, i, l
71 character(len=70) :: aux_s
72
73 push_sub(ps_psf_file_read)
74
75 ! formats used in this routine
768000 format(1x,i2)
779000 format(1x,a2,1x,a2,1x,a3,1x,a4)
789010 format(1x,6a10,/,1x,a70)
799015 format(1x,2i3,i5,3f20.10)
809030 format(4(g20.12))
819040 format(1x,a)
82
83 ! Reads the header line of the file, with general info about the ps.
84 if (ascii) then
85 read(unit, 9000) psf%namatm, psf%icorr, psf%irel, psf%icore
86 read(unit, 9010) (psf%method(l),l=1,6), psf%title
87 read(unit, 9015) psf%npotd, psf%npotu, psf%nr, psf%b, psf%a, psf%zval
88 else
89 read(unit) psf%namatm, psf%icorr, psf%irel, psf%icore, &
90 (psf%method(l), l=1, 6), psf%title, psf%npotd, psf%npotu, &
91 psf%nr, psf%b, psf%a, psf%zval
92 end if
93
94 ! add extra point for the zero
95 psf%nr = psf%nr + 1
96
97 ! Allocates the variables to psf%nr: ! Reads the pseudo-valence charge density, in bohr^(-3)
98 ! rho_val(1:nrval) : pseudo-valence charge distribution
99 safe_allocate(psf%rofi (1:psf%nr))
100 safe_allocate(psf%vps (1:psf%nr, 1:psf%npotd))
101 safe_allocate(psf%chcore (1:psf%nr))
102 safe_allocate(psf%rho_val(1:psf%nr))
103 safe_allocate(psf%vso (1:psf%nr, 1:psf%npotu))
104
105 ! Reads the radial values, in bohrs
106 ! rofi(1:nr) : radial values ( rofi(i) = b*( exp(a*(i-1)) - 1 ) ) [bohr]
107 if (ascii) then
108 read(unit, 9040) aux_s
109 read(unit, 9030) (psf%rofi(i), i=2, psf%nr)
110 else
111 read(unit) (psf%rofi(i), i=2, psf%nr)
112 end if
113 psf%rofi(1) = m_zero
115 ! Reads the pseudoptential functions, times r, in Rydberg*bohr.
116 ! Inmediately afterwards, it is divided by r, so that its final units are Rydbergs
117 do ndown = 1, psf%npotd
118 if (ascii) then
119 read(unit, 9040) aux_s
120 read(unit, 8000) l
121 read(unit, 9030) (psf%vps(i, ndown), i=2, psf%nr)
122 else
123 read(unit) l, (psf%vps(i, ndown), i=2, psf%nr)
124 end if
125
126 if (l /= ndown-1) then
127 message(1) = 'Unexpected angular momentum'
128 message(2) = 'Pseudopotential should be ordered by increasing l'
129 call messages_warning(2, namespace=namespace)
130 end if
131
132 psf%vps(2:, ndown) = psf%vps(2:, ndown) / psf%rofi(2:)
133 psf%vps(1, ndown) = first_point_extrapolate(psf%rofi, psf%vps(:, ndown))
134 end do
136 ! Reads --or skips-- the "down" pseudopotentials.
137 do nup = 1, psf%npotu
138 if (ascii) then
139 read(unit, 9040) aux_s
140 read(unit, 8000) l
141 read(unit, 9030) (psf%vso(i, nup), i=2, psf%nr)
142 else
143 read(unit) l, (psf%vso(i, nup), i=2, psf%nr)
144 end if
146 if ((l /= nup) .and. (psf%irel == 'rel')) then
147 message(1) = 'Unexpected angular momentum'
148 message(2) = 'Pseudopotential should be ordered by increasing l'
149 call messages_warning(2, namespace=namespace)
150 end if
152 psf%vso(2:, nup) = psf%vso(2:, nup) / psf%rofi(2:)
153 psf%vso(1, nup) = first_point_extrapolate(psf%rofi, psf%vso(:, nup))
154
155 end do
156 if (psf%irel /= 'rel') then
157 psf%vso(:,:) = m_zero
158 end if
159
160 ! Reads the core correcction charge density, in bohr^(-3)
161 ! chcore(1:nrval) : core-correction charge distribution
162 if (ascii) then
163 read(unit, 9040) aux_s
164 read(unit, 9030) (psf%chcore(i), i=2, psf%nr)
165 else
166 read(unit) (psf%chcore(i), i=2, psf%nr)
167 end if
168
169 psf%chcore(1) = first_point_extrapolate(psf%rofi, psf%chcore)
170
171 ! Reads the pseudo-valence charge density, in bohr^(-3)
172 ! rho_val(1:nrval) : pseudo-valence charge distribution
173 ! rho_val(1:nrval) : pseudo-valence charge distribution
174 if (ascii) then
175 read(unit, 9040) aux_s
176 read(unit, 9030) (psf%rho_val(i), i=2, psf%nr)
177 else
178 read(unit) (psf%rho_val(i), i=2, psf%nr)
179 end if
180
181 psf%rho_val(1) = first_point_extrapolate(psf%rofi, psf%rho_val)
182
183 pop_sub(ps_psf_file_read)
184 end subroutine ps_psf_file_read
185
186
187 ! ---------------------------------------------------------
188 subroutine ps_psf_file_end(psf)
189 type(ps_psf_file_t), intent(inout) :: psf
190
191 safe_deallocate_a(psf%rofi)
192 safe_deallocate_a(psf%vps)
193 safe_deallocate_a(psf%chcore)
194 safe_deallocate_a(psf%rho_val)
195 safe_deallocate_a(psf%vso)
196
197 end subroutine ps_psf_file_end
198
199end module ps_psf_file_oct_m
200
201!! Local Variables:
202!! mode: f90
203!! coding: utf-8
204!! End:
real(real64), parameter, public m_zero
Definition: global.F90:187
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
real(real64) function, public first_point_extrapolate(x, y, high_order)
Definition: ps_in_grid.F90:437
subroutine, public ps_psf_file_end(psf)
subroutine, public ps_psf_file_read(unit, ascii, psf, namespace)