Line data Source code
1 : !--------------------------------------------------------------------------------------------------!
2 : ! CP2K: A general program to perform molecular dynamics simulations !
3 : ! Copyright 2000-2025 CP2K developers group <https://cp2k.org> !
4 : ! !
5 : ! SPDX-License-Identifier: GPL-2.0-or-later !
6 : !--------------------------------------------------------------------------------------------------!
7 : ! **************************************************************************************************
8 : MODULE integration_grid_types
9 :
10 : USE kinds, ONLY: dp
11 : #include "./base/base_uses.f90"
12 :
13 : IMPLICIT NONE
14 :
15 : PRIVATE
16 :
17 : CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'integration_grid_types'
18 :
19 : TYPE grid_batch_val_1d_type
20 : INTEGER :: np1 = -1
21 : REAL(KIND=dp), DIMENSION(:), ALLOCATABLE :: val1d
22 : END TYPE grid_batch_val_1d_type
23 :
24 : TYPE grid_batch_val_2d_type
25 : INTEGER :: np1 = -1, np2 = -1
26 : REAL(KIND=dp), DIMENSION(:, :), ALLOCATABLE :: val2d
27 : END TYPE grid_batch_val_2d_type
28 :
29 : TYPE gnlist_type
30 : INTEGER, DIMENSION(:), ALLOCATABLE :: atom_list
31 : REAL(KIND=dp), DIMENSION(:, :), ALLOCATABLE :: atom_pos
32 : END TYPE gnlist_type
33 :
34 : TYPE grid_batch_info_type
35 : INTEGER :: np = -1
36 : INTEGER :: ref_atom = -1
37 : INTEGER :: ibatch = -1
38 : TYPE(gnlist_type) :: gnlist = gnlist_type()
39 : REAL(KIND=dp), DIMENSION(3) :: rcenter = 0.0_dp
40 : REAL(KIND=dp) :: radius = 0.0_dp
41 : REAL(dp), DIMENSION(:, :), ALLOCATABLE :: rco
42 : REAL(dp), DIMENSION(:), ALLOCATABLE :: weight
43 : REAL(dp), DIMENSION(:), ALLOCATABLE :: wref
44 : REAL(dp), DIMENSION(:), ALLOCATABLE :: wsum
45 : END TYPE grid_batch_info_type
46 :
47 : TYPE integration_grid_type
48 : INTEGER :: nbatch = -1
49 : TYPE(grid_batch_info_type), DIMENSION(:), ALLOCATABLE :: grid_batch
50 : END TYPE integration_grid_type
51 :
52 : TYPE integration_grid_value_type
53 : INTEGER :: nbatch = -1
54 : TYPE(grid_batch_val_1d_type), DIMENSION(:), ALLOCATABLE :: grid_val_1d
55 : TYPE(grid_batch_val_2d_type), DIMENSION(:), ALLOCATABLE :: grid_val_2d
56 : END TYPE integration_grid_value_type
57 :
58 : PUBLIC :: integration_grid_type, allocate_intgrid, deallocate_intgrid
59 : PUBLIC :: integration_grid_value_type, allocate_intgrid_val, deallocate_intgrid_val
60 :
61 : ! **************************************************************************************************
62 :
63 : CONTAINS
64 :
65 : ! **************************************************************************************************
66 : !> \brief Initialize integration_grid_type
67 : !> \param int_grid ...
68 : !> \date 02.2018
69 : !> \param
70 : !> \author JGH
71 : !> \version 1.0
72 : ! **************************************************************************************************
73 4 : SUBROUTINE allocate_intgrid(int_grid)
74 :
75 : TYPE(integration_grid_type), POINTER :: int_grid
76 :
77 4 : IF (ASSOCIATED(int_grid)) CALL deallocate_intgrid(int_grid)
78 4 : ALLOCATE (int_grid)
79 4 : int_grid%nbatch = 0
80 :
81 4 : END SUBROUTINE allocate_intgrid
82 :
83 : ! **************************************************************************************************
84 : !> \brief Deallocate integration_grid_type
85 : !> \param int_grid ...
86 : !> \date 02.2018
87 : !> \param
88 : !> \author JGH
89 : !> \version 1.0
90 : ! **************************************************************************************************
91 4 : SUBROUTINE deallocate_intgrid(int_grid)
92 : TYPE(integration_grid_type), POINTER :: int_grid
93 :
94 : INTEGER :: i
95 :
96 4 : IF (ASSOCIATED(int_grid)) THEN
97 4 : IF (ALLOCATED(int_grid%grid_batch)) THEN
98 884 : DO i = 1, int_grid%nbatch
99 880 : IF (ALLOCATED(int_grid%grid_batch(i)%rco)) DEALLOCATE (int_grid%grid_batch(i)%rco)
100 880 : IF (ALLOCATED(int_grid%grid_batch(i)%weight)) DEALLOCATE (int_grid%grid_batch(i)%weight)
101 880 : IF (ALLOCATED(int_grid%grid_batch(i)%wref)) DEALLOCATE (int_grid%grid_batch(i)%wref)
102 880 : IF (ALLOCATED(int_grid%grid_batch(i)%wsum)) DEALLOCATE (int_grid%grid_batch(i)%wsum)
103 : !
104 880 : IF (ALLOCATED(int_grid%grid_batch(i)%gnlist%atom_list)) DEALLOCATE (int_grid%grid_batch(i)%gnlist%atom_list)
105 884 : IF (ALLOCATED(int_grid%grid_batch(i)%gnlist%atom_pos)) DEALLOCATE (int_grid%grid_batch(i)%gnlist%atom_pos)
106 : END DO
107 884 : DEALLOCATE (int_grid%grid_batch)
108 : END IF
109 4 : DEALLOCATE (int_grid)
110 : ELSE
111 : CALL cp_abort(__LOCATION__, &
112 : "The pointer int_grid is not associated and "// &
113 0 : "cannot be deallocated")
114 : END IF
115 4 : END SUBROUTINE deallocate_intgrid
116 :
117 : ! **************************************************************************************************
118 : !> \brief Initialize integration_grid_value_type
119 : !> \param int_grid ...
120 : !> \date 02.2018
121 : !> \param
122 : !> \author JGH
123 : !> \version 1.0
124 : ! **************************************************************************************************
125 0 : SUBROUTINE allocate_intgrid_val(int_grid)
126 :
127 : TYPE(integration_grid_value_type), POINTER :: int_grid
128 :
129 0 : IF (ASSOCIATED(int_grid)) CALL deallocate_intgrid_val(int_grid)
130 0 : ALLOCATE (int_grid)
131 0 : int_grid%nbatch = 0
132 :
133 0 : END SUBROUTINE allocate_intgrid_val
134 :
135 : ! **************************************************************************************************
136 : !> \brief Deallocate integration_grid_value_type
137 : !> \param int_grid ...
138 : !> \date 02.2018
139 : !> \param
140 : !> \author JGH
141 : !> \version 1.0
142 : ! **************************************************************************************************
143 0 : SUBROUTINE deallocate_intgrid_val(int_grid)
144 : TYPE(integration_grid_value_type), POINTER :: int_grid
145 :
146 : INTEGER :: i
147 :
148 0 : IF (ASSOCIATED(int_grid)) THEN
149 0 : IF (ALLOCATED(int_grid%grid_val_1d)) THEN
150 0 : DO i = 1, int_grid%nbatch
151 0 : IF (ALLOCATED(int_grid%grid_val_1d(i)%val1d)) DEALLOCATE (int_grid%grid_val_1d(i)%val1d)
152 : END DO
153 0 : DEALLOCATE (int_grid%grid_val_1d)
154 : END IF
155 0 : IF (ALLOCATED(int_grid%grid_val_2d)) THEN
156 0 : DO i = 1, int_grid%nbatch
157 0 : IF (ALLOCATED(int_grid%grid_val_2d(i)%val2d)) DEALLOCATE (int_grid%grid_val_2d(i)%val2d)
158 : END DO
159 0 : DEALLOCATE (int_grid%grid_val_2d)
160 : END IF
161 0 : DEALLOCATE (int_grid)
162 : ELSE
163 : CALL cp_abort(__LOCATION__, &
164 : "The pointer int_grid is not associated and "// &
165 0 : "cannot be deallocated")
166 : END IF
167 0 : END SUBROUTINE deallocate_intgrid_val
168 :
169 0 : END MODULE integration_grid_types
|