68 CHARACTER(len=*),
PARAMETER :: routinen =
'atom_pseudo_opt'
70 CHARACTER(LEN=2) :: elem
71 CHARACTER(LEN=default_string_length), &
72 DIMENSION(:),
POINTER :: tmpstringlist
73 INTEGER :: ads, do_eric, do_erie, handle, i, im, &
74 in, iw, k, l, maxl, mb, method, mo, &
75 n_meth, n_rep, nr_gh, reltyp, zcore, &
77 INTEGER,
DIMENSION(0:lmat) :: maxn
78 INTEGER,
DIMENSION(:),
POINTER :: cn
79 LOGICAL :: do_gh, eri_c, eri_e,
graph, pp_calc
80 REAL(kind=
dp) :: ne, nm
81 REAL(kind=
dp),
DIMENSION(0:lmat, 10) :: pocc
86 TYPE(
atom_p_type),
DIMENSION(:, :),
POINTER :: atom_info, atom_refs
91 opt_section, potential_section, &
92 powell_section, xc_section
94 CALL timeset(routinen, handle)
101 IF (
ptable(i)%symbol == elem)
THEN
106 IF (zz /= 1) zval = zz
109 ALLOCATE (ae_basis, pp_basis)
111 NULLIFY (ae_basis%grid)
113 NULLIFY (pp_basis%grid)
120 IF (iw > 0)
CALL atom_print_info(zval,
"Atomic Energy Calculation", iw)
130 NULLIFY (potential_section)
132 ALLOCATE (ae_pot, p_pot)
135 IF (.NOT. p_pot%confinement .AND. .NOT. ae_pot%confinement)
THEN
137 p_pot%confinement = .true.
142 p_pot%rcon = (2._dp*
ptable(zval)%covalent_radius*
bohr)**2
143 ae_pot%confinement = .true.
148 ae_pot%rcon = (2._dp*
ptable(zval)%covalent_radius*
bohr)**2
165 DO in = 1, min(
SIZE(cn), 4)
166 maxn(in - 1) = cn(in)
169 maxn(in) = min(maxn(in), ae_basis%nbas(in))
183 ALLOCATE (ae_int, pp_int)
185 ALLOCATE (atom_info(n_rep, n_meth), atom_refs(n_rep, n_meth))
189 WRITE (iw,
'(/," ",79("*"))')
190 WRITE (iw,
'(" ",26("*"),A,25("*"))')
" Calculate Reference States "
191 WRITE (iw,
'(" ",79("*"))')
198 NULLIFY (atom_info(in, im)%atom, atom_refs(in, im)%atom)
202 atom_info(in, im)%atom%optimization = optimization
203 atom_refs(in, im)%atom%optimization = optimization
205 atom_info(in, im)%atom%z = zval
206 atom_refs(in, im)%atom%z = zval
208 atom_info(in, im)%atom%xc_section => xc_section
209 atom_refs(in, im)%atom%xc_section => xc_section
211 ALLOCATE (state, statepp)
215 c_vals=tmpstringlist)
217 pp_calc = index(tmpstringlist(1),
"CORE") /= 0
218 cpassert(.NOT. pp_calc)
225 state%maxl_calc = max(maxl, state%maxl_occ)
226 state%maxl_calc = min(
lmat, state%maxl_calc)
228 DO k = 0, state%maxl_calc
230 IF (state%maxn_occ(k) == 0) ads = 1
231 state%maxn_calc(k) = max(maxn(k), state%maxn_occ(k) + ads)
232 state%maxn_calc(k) = min(state%maxn_calc(k), ae_basis%nbas(k))
235 CALL set_atom(atom_refs(in, im)%atom, zcore=zval, pp_calc=.false.)
237 IF (state%multiplicity /= -1)
THEN
242 nm = real((2*l + 1), kind=
dp)
244 ne = state%occupation(l, k)
245 IF (ne == 0._dp)
THEN
247 ELSEIF (ne == 2._dp*nm)
THEN
248 state%occa(l, k) = nm
249 state%occb(l, k) = nm
250 ELSEIF (state%multiplicity == -2)
THEN
251 state%occa(l, k) = min(ne, nm)
252 state%occb(l, k) = max(0._dp, ne - nm)
254 state%occa(l, k) = 0.5_dp*(ne + state%multiplicity - 1._dp)
255 state%occb(l, k) = ne - state%occa(l, k)
264 zcore = zval - nint(sum(statepp%core))
265 CALL set_atom(atom_info(in, im)%atom, zcore=zcore, pp_calc=.true.)
267 statepp%occ = state%occ - statepp%core
268 statepp%occupation = 0._dp
272 IF (statepp%occ(l, i) /= 0._dp)
THEN
274 statepp%occupation(l, k) = state%occ(l, i)
275 IF (state%multiplicity /= -1)
THEN
276 statepp%occa(l, k) = state%occa(l, i) - statepp%core(l, i)/2
277 statepp%occb(l, k) = state%occb(l, i) - statepp%core(l, i)/2
285 statepp%maxl_calc = state%maxl_calc
286 statepp%maxn_calc = 0
288 DO k = 0, statepp%maxl_calc
289 statepp%maxn_calc(k) = state%maxn_calc(k) - maxn(k)
290 statepp%maxn_calc(k) = min(statepp%maxn_calc(k), pp_basis%nbas(k))
292 statepp%multiplicity = state%multiplicity
296 CALL set_atom(atom_info(in, im)%atom, method_type=method)
297 CALL set_atom(atom_refs(in, im)%atom, method_type=method, relativistic=reltyp)
301 CALL atom_int_setup(pp_int, pp_basis, potential=p_pot, eri_coulomb=eri_c, eri_exchange=eri_e)
303 NULLIFY (pp_int%tzora, pp_int%hdkh)
307 CALL set_atom(atom_info(in, im)%atom, basis=pp_basis, integrals=pp_int, potential=p_pot)
308 statepp%maxn_calc(:) = min(statepp%maxn_calc(:), pp_basis%nbas(:))
309 cpassert(all(state%maxn_calc(:) >= state%maxn_occ))
314 eri_coulomb=eri_c, eri_exchange=eri_e)
320 CALL set_atom(atom_refs(in, im)%atom, basis=ae_basis, integrals=ae_int, potential=ae_pot)
321 state%maxn_calc(:) = min(state%maxn_calc(:), ae_basis%nbas(:))
322 cpassert(all(state%maxn_calc(:) >= state%maxn_occ))
324 CALL set_atom(atom_info(in, im)%atom, coulomb_integral_type=do_eric, &
325 exchange_integral_type=do_erie)
326 CALL set_atom(atom_refs(in, im)%atom, coulomb_integral_type=do_eric, &
327 exchange_integral_type=do_erie)
328 atom_info(in, im)%atom%hfx_pot%do_gh = do_gh
329 atom_info(in, im)%atom%hfx_pot%nr_gh = nr_gh
330 atom_refs(in, im)%atom%hfx_pot%do_gh = do_gh
331 atom_refs(in, im)%atom%hfx_pot%nr_gh = nr_gh
333 CALL set_atom(atom_info(in, im)%atom, state=statepp)
335 mo = maxval(statepp%maxn_calc)
336 mb = maxval(atom_info(in, im)%atom%basis%nbas)
338 CALL set_atom(atom_info(in, im)%atom, orbitals=orbitals)
340 CALL set_atom(atom_refs(in, im)%atom, state=state)
342 mo = maxval(state%maxn_calc)
343 mb = maxval(atom_refs(in, im)%atom%basis%nbas)
345 CALL set_atom(atom_refs(in, im)%atom, orbitals=orbitals)
347 IF (
atom_consistent_method(atom_refs(in, im)%atom%method_type, atom_refs(in, im)%atom%state%multiplicity))
THEN
362 WRITE (iw,
'(/," ",79("*"))')
363 WRITE (iw,
'(" ",21("*"),A,21("*"))')
" Optimize Pseudopotential Parameters "
364 WRITE (iw,
'(" ",79("*"))')
417 DEALLOCATE (atom_info, atom_refs)
419 DEALLOCATE (ae_pot, p_pot, ae_basis, pp_basis, ae_int, pp_int)
421 CALL timestop(handle)