(git:374b731)
Loading...
Searching...
No Matches
tip_scan_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
11 USE kinds, ONLY: default_string_length,&
12 dp
13 USE pw_types, ONLY: pw_c1d_gs_type,&
15#include "./base/base_uses.f90"
16
17 IMPLICIT NONE
18
19 PRIVATE
20
21 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'tip_scan_types'
22
24
25! **************************************************************************************************
27 INTEGER :: num_scan_points
28 REAL(kind=dp), DIMENSION(3) :: ref_point
29 REAL(kind=dp), DIMENSION(:, :), &
30 ALLOCATABLE :: tip_pos
31 CHARACTER(LEN=default_string_length) :: tip_cube_file
32 TYPE(pw_r3d_rs_type), POINTER :: tip_pw_r
33 TYPE(pw_c1d_gs_type), POINTER :: tip_pw_g
34 END TYPE scanning_type
35! **************************************************************************************************
36
37CONTAINS
38
39! **************************************************************************************************
40!> \brief ...
41!> \param scan_info ...
42!> \param input_section ...
43! **************************************************************************************************
44 SUBROUTINE read_scanning_section(scan_info, input_section)
45
46 TYPE(scanning_type), INTENT(INOUT) :: scan_info
47 TYPE(section_vals_type), POINTER :: input_section
48
49 CHARACTER(LEN=default_string_length) :: schar
50 INTEGER :: ii, ix, iy, iz, nx, ny, nz
51 INTEGER, DIMENSION(:), POINTER :: ilist
52 REAL(kind=dp) :: dx, dy, dz
53 REAL(kind=dp), DIMENSION(:), POINTER :: rlist, rpoint
54
55 CALL section_vals_val_get(input_section, "SCAN_DIRECTION", c_val=schar)
56 CALL section_vals_val_get(input_section, "REFERENCE_POINT", r_vals=rpoint)
57 CALL section_vals_val_get(input_section, "SCAN_POINTS", i_vals=ilist)
58 CALL section_vals_val_get(input_section, "SCAN_STEP", r_vals=rlist)
59
60 nx = 1
61 ny = 1
62 nz = 1
63
64 dx = 0.0_dp
65 dy = 0.0_dp
66 dz = 0.0_dp
67
68 SELECT CASE (schar)
69 CASE ("X")
70 cpassert(SIZE(ilist) >= 1)
71 cpassert(SIZE(rlist) >= 1)
72 nx = ilist(1)
73 dx = rlist(1)
74 CASE ("Y")
75 cpassert(SIZE(ilist) >= 1)
76 cpassert(SIZE(rlist) >= 1)
77 ny = ilist(1)
78 dy = rlist(1)
79 CASE ("Z")
80 cpassert(SIZE(ilist) >= 1)
81 cpassert(SIZE(rlist) >= 1)
82 nz = ilist(1)
83 dz = rlist(1)
84 CASE ("XY")
85 cpassert(SIZE(ilist) >= 2)
86 cpassert(SIZE(rlist) >= 2)
87 nx = ilist(1)
88 ny = ilist(2)
89 dx = rlist(1)
90 dy = rlist(2)
91 CASE ("XZ")
92 cpassert(SIZE(ilist) >= 2)
93 cpassert(SIZE(rlist) >= 2)
94 nx = ilist(1)
95 nz = ilist(2)
96 dx = rlist(1)
97 dz = rlist(2)
98 CASE ("YZ")
99 cpassert(SIZE(ilist) >= 2)
100 cpassert(SIZE(rlist) >= 2)
101 ny = ilist(1)
102 nz = ilist(2)
103 dy = rlist(1)
104 dz = rlist(2)
105 CASE ("XYZ")
106 cpassert(SIZE(ilist) >= 3)
107 cpassert(SIZE(rlist) >= 3)
108 nx = ilist(1)
109 ny = ilist(2)
110 nz = ilist(3)
111 dx = rlist(1)
112 dy = rlist(2)
113 dz = rlist(3)
114 CASE DEFAULT
115 cpabort("Invalid Scan Type")
116 END SELECT
117
118 scan_info%ref_point(1:3) = rpoint(1:3)
119 scan_info%num_scan_points = nx*ny*nz
120 ALLOCATE (scan_info%tip_pos(3, nx*ny*nz))
121 rpoint(1) = rpoint(1) - 0.5_dp*(nx - 1)*dx
122 rpoint(2) = rpoint(2) - 0.5_dp*(ny - 1)*dy
123 rpoint(3) = rpoint(3) - 0.5_dp*(nz - 1)*dz
124
125 ii = 0
126 DO iz = 1, nz
127 DO iy = 1, ny
128 DO ix = 1, nx
129 ii = ii + 1
130 scan_info%tip_pos(1, ii) = rpoint(1) + (ix - 1)*dx
131 scan_info%tip_pos(2, ii) = rpoint(2) + (iy - 1)*dy
132 scan_info%tip_pos(3, ii) = rpoint(3) + (iz - 1)*dz
133 END DO
134 END DO
135 END DO
136
137 ! tip potential file name
138 CALL section_vals_val_get(input_section, "TIP_FILENAME", c_val=schar)
139 scan_info%tip_cube_file = schar
140
141 NULLIFY (scan_info%tip_pw_r)
142 NULLIFY (scan_info%tip_pw_g)
143
144 END SUBROUTINE read_scanning_section
145
146! **************************************************************************************************
147!> \brief ...
148!> \param scan_info ...
149! **************************************************************************************************
150 SUBROUTINE release_scanning_type(scan_info)
151
152 TYPE(scanning_type), INTENT(INOUT) :: scan_info
153
154 scan_info%num_scan_points = 0
155 scan_info%ref_point = 0.0_dp
156 IF (ALLOCATED(scan_info%tip_pos)) THEN
157 DEALLOCATE (scan_info%tip_pos)
158 END IF
159 IF (ASSOCIATED(scan_info%tip_pw_r)) THEN
160 CALL scan_info%tip_pw_r%release()
161 DEALLOCATE (scan_info%tip_pw_r)
162 END IF
163 IF (ASSOCIATED(scan_info%tip_pw_g)) THEN
164 CALL scan_info%tip_pw_g%release()
165 DEALLOCATE (scan_info%tip_pw_g)
166 END IF
167
168 END SUBROUTINE release_scanning_type
169
170END MODULE tip_scan_types
objects that represent the structure of input sections and the data contained in an input section
subroutine, public section_vals_val_get(section_vals, keyword_name, i_rep_section, i_rep_val, n_rep_val, val, l_val, i_val, r_val, c_val, l_vals, i_vals, r_vals, c_vals, explicit)
returns the requested value
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
integer, parameter, public default_string_length
Definition kinds.F:57
subroutine, public release_scanning_type(scan_info)
...
subroutine, public read_scanning_section(scan_info, input_section)
...