Line data Source code
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 : !> \brief Storage to keep precomputed surface Green's functions
10 : ! **************************************************************************************************
11 : MODULE negf_green_cache
12 : USE cp_cfm_types, ONLY: cp_cfm_release,&
13 : cp_cfm_type
14 : USE kinds, ONLY: dp
15 : USE util, ONLY: sort
16 : #include "./base/base_uses.f90"
17 :
18 : IMPLICIT NONE
19 : PRIVATE
20 :
21 : CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'negf_green_cache'
22 : LOGICAL, PARAMETER, PRIVATE :: debug_this_module = .TRUE.
23 :
24 : PUBLIC :: green_functions_cache_type
25 :
26 : PUBLIC :: green_functions_cache_expand, &
27 : green_functions_cache_reorder, &
28 : green_functions_cache_release
29 :
30 : ! **************************************************************************************************
31 : !> \brief Storage to keep surface Green's functions.
32 : !> \author Sergey Chulkov
33 : ! **************************************************************************************************
34 : TYPE green_functions_cache_type
35 : !> retarded surface Green's functions [ncontacts, nnodes]
36 : TYPE(cp_cfm_type), ALLOCATABLE, DIMENSION(:, :) :: g_surf_contacts
37 : !> list of points over the normalised interval [-1 .. 1].
38 : !> Coordinates of actual point where Green's functions were evaluated
39 : !> can be obtained by using an appropriate rescale_nodes_*() subroutine
40 : !> from the module 'negf_integr_utils'.
41 : REAL(kind=dp), ALLOCATABLE, DIMENSION(:) :: tnodes
42 : END TYPE green_functions_cache_type
43 :
44 : CONTAINS
45 : ! **************************************************************************************************
46 : !> \brief Reallocate storage so it can handle extra 'nnodes_extra' items for each contact.
47 : !> \param cache storage to expand
48 : !> \param ncontacts number of contacts
49 : !> \param nnodes_extra number of items to add
50 : !> \author Sergey Chulkov
51 : ! **************************************************************************************************
52 612 : SUBROUTINE green_functions_cache_expand(cache, ncontacts, nnodes_extra)
53 : TYPE(green_functions_cache_type), INTENT(inout) :: cache
54 : INTEGER, INTENT(in) :: ncontacts, nnodes_extra
55 :
56 : INTEGER :: nentries_exist
57 : LOGICAL :: is_alloc
58 612 : TYPE(cp_cfm_type), ALLOCATABLE, DIMENSION(:, :) :: g_surf_contacts
59 :
60 612 : is_alloc = ALLOCATED(cache%g_surf_contacts)
61 :
62 612 : IF (is_alloc) THEN
63 164 : CPASSERT(SIZE(cache%g_surf_contacts, 1) == ncontacts)
64 164 : nentries_exist = SIZE(cache%g_surf_contacts, 2)
65 :
66 : ELSE
67 : nentries_exist = 0
68 : END IF
69 :
70 45858 : ALLOCATE (g_surf_contacts(ncontacts, nentries_exist + nnodes_extra))
71 :
72 612 : IF (is_alloc) THEN
73 23744 : g_surf_contacts(1:ncontacts, 1:nentries_exist) = cache%g_surf_contacts(1:ncontacts, 1:nentries_exist)
74 164 : DEALLOCATE (cache%g_surf_contacts)
75 : END IF
76 :
77 612 : CALL MOVE_ALLOC(g_surf_contacts, cache%g_surf_contacts)
78 612 : END SUBROUTINE green_functions_cache_expand
79 :
80 : ! **************************************************************************************************
81 : !> \brief Sort cached items in ascending order.
82 : !> \param cache storage to reorder
83 : !> \param tnodes coordinate of items in storage
84 : !> \author Sergey Chulkov
85 : ! **************************************************************************************************
86 72 : SUBROUTINE green_functions_cache_reorder(cache, tnodes)
87 : TYPE(green_functions_cache_type), INTENT(inout) :: cache
88 : REAL(kind=dp), DIMENSION(:), INTENT(in) :: tnodes
89 :
90 : INTEGER :: ind_new, ind_old, ncontacts, nnodes
91 72 : INTEGER, ALLOCATABLE, DIMENSION(:) :: indices
92 72 : TYPE(cp_cfm_type), ALLOCATABLE, DIMENSION(:, :) :: g_surf_contacts
93 :
94 72 : nnodes = SIZE(tnodes)
95 :
96 72 : CPASSERT(ALLOCATED(cache%g_surf_contacts))
97 72 : CPASSERT(SIZE(cache%g_surf_contacts, 2) == nnodes)
98 :
99 72 : ncontacts = SIZE(cache%g_surf_contacts, 1)
100 :
101 72 : IF (ALLOCATED(cache%tnodes)) DEALLOCATE (cache%tnodes)
102 :
103 11976 : ALLOCATE (g_surf_contacts(ncontacts, nnodes))
104 216 : ALLOCATE (cache%tnodes(nnodes))
105 216 : ALLOCATE (indices(nnodes))
106 :
107 3968 : cache%tnodes(:) = tnodes(:)
108 72 : CALL sort(cache%tnodes, nnodes, indices)
109 :
110 3968 : DO ind_new = 1, nnodes
111 3896 : ind_old = indices(ind_new)
112 11760 : g_surf_contacts(1:ncontacts, ind_new) = cache%g_surf_contacts(1:ncontacts, ind_old)
113 : END DO
114 :
115 72 : CALL MOVE_ALLOC(g_surf_contacts, cache%g_surf_contacts)
116 72 : END SUBROUTINE green_functions_cache_reorder
117 :
118 : ! **************************************************************************************************
119 : !> \brief Release storage.
120 : !> \param cache storage to release
121 : !> \author Sergey Chulkov
122 : ! **************************************************************************************************
123 452 : SUBROUTINE green_functions_cache_release(cache)
124 : TYPE(green_functions_cache_type), INTENT(inout) :: cache
125 :
126 : INTEGER :: icontact, ipoint, ncontacts
127 :
128 452 : IF (ALLOCATED(cache%tnodes)) DEALLOCATE (cache%tnodes)
129 :
130 452 : IF (ALLOCATED(cache%g_surf_contacts)) THEN
131 448 : ncontacts = SIZE(cache%g_surf_contacts, 1)
132 7058 : DO ipoint = SIZE(cache%g_surf_contacts, 2), 1, -1
133 20278 : DO icontact = ncontacts, 1, -1
134 19830 : CALL cp_cfm_release(cache%g_surf_contacts(icontact, ipoint))
135 : END DO
136 : END DO
137 :
138 448 : DEALLOCATE (cache%g_surf_contacts)
139 : END IF
140 452 : END SUBROUTINE green_functions_cache_release
141 0 : END MODULE negf_green_cache
142 :
|