(git:374b731)
Loading...
Searching...
No Matches
paw_basis_types.F
Go to the documentation of this file.
1!--------------------------------------------------------------------------------------------------!
2! CP2K: A general program to perform molecular dynamics simulations !
3! Copyright 2000-2024 CP2K developers group <https://cp2k.org> !
4! !
5! SPDX-License-Identifier: GPL-2.0-or-later !
6!--------------------------------------------------------------------------------------------------!
7
8! **************************************************************************************************
9!> \par History
10!> none
11!> \author JGH (9.2022)
12! **************************************************************************************************
14
17 USE orbital_pointers, ONLY: nso,&
18 nsoset
19#include "../base/base_uses.f90"
20
21 IMPLICIT NONE
22
23 PRIVATE
24
25 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'paw_basis_types'
26
27 PUBLIC :: get_paw_basis_info
28
29CONTAINS
30
31! **************************************************************************************************
32!> \brief Return some info on the PAW basis derived from a GTO basis set
33!> \param basis_1c The parent GTO basis set
34!> \param o2nindex ...
35!> \param n2oindex ...
36!> \param nsatbas ...
37!> \version 1.0
38! **************************************************************************************************
39 SUBROUTINE get_paw_basis_info(basis_1c, o2nindex, n2oindex, nsatbas)
40
41 TYPE(gto_basis_set_type), INTENT(IN) :: basis_1c
42 INTEGER, DIMENSION(:), OPTIONAL, POINTER :: o2nindex, n2oindex
43 INTEGER, INTENT(OUT), OPTIONAL :: nsatbas
44
45 INTEGER :: ico, ipgf, iset, iso, iso_pgf, iso_set, &
46 k, lx, maxso, nset, nsox
47 INTEGER, DIMENSION(:), POINTER :: lmax, lmin, npgf
48 LOGICAL :: n2o, nsa, o2n
49
50 o2n = PRESENT(o2nindex)
51 n2o = PRESENT(n2oindex)
52 nsa = PRESENT(nsatbas)
53
54 IF (o2n .OR. n2o .OR. nsa) THEN
55 CALL get_gto_basis_set(gto_basis_set=basis_1c, &
56 nset=nset, lmax=lmax, lmin=lmin, npgf=npgf, maxso=maxso)
57
58 ! Index transformation OLD-NEW
59 IF (o2n) THEN
60 ALLOCATE (o2nindex(maxso*nset))
61 o2nindex = 0
62 END IF
63 IF (n2o) THEN
64 ALLOCATE (n2oindex(maxso*nset))
65 n2oindex = 0
66 END IF
67
68 ico = 1
69 DO iset = 1, nset
70 iso_set = (iset - 1)*maxso + 1
71 nsox = nsoset(lmax(iset))
72 DO ipgf = 1, npgf(iset)
73 iso_pgf = iso_set + (ipgf - 1)*nsox
74 iso = iso_pgf + nsoset(lmin(iset) - 1)
75 DO lx = lmin(iset), lmax(iset)
76 DO k = 1, nso(lx)
77 IF (n2o) n2oindex(ico) = iso
78 IF (o2n) o2nindex(iso) = ico
79 iso = iso + 1
80 ico = ico + 1
81 END DO
82 END DO
83 END DO
84 END DO
85 IF (nsa) nsatbas = ico - 1
86 END IF
87
88 END SUBROUTINE get_paw_basis_info
89
90END MODULE paw_basis_types
subroutine, public get_gto_basis_set(gto_basis_set, name, aliases, norm_type, kind_radius, ncgf, nset, nsgf, cgf_symbol, sgf_symbol, norm_cgf, set_radius, lmax, lmin, lx, ly, lz, m, ncgf_set, npgf, nsgf_set, nshell, cphi, pgf_radius, sphi, scon, zet, first_cgf, first_sgf, l, last_cgf, last_sgf, n, gcc, maxco, maxl, maxpgf, maxsgf_set, maxshell, maxso, nco_sum, npgf_sum, nshell_sum, maxder, short_kind_radius)
...
Provides Cartesian and spherical orbital pointers and indices.
integer, dimension(:), allocatable, public nsoset
integer, dimension(:), allocatable, public nso
subroutine, public get_paw_basis_info(basis_1c, o2nindex, n2oindex, nsatbas)
Return some info on the PAW basis derived from a GTO basis set.