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 builds the input structure for the EMBED environment: clone of MIXED environment
10 : !> \author Vladimir Rybkin - University of Zurich
11 : ! **************************************************************************************************
12 : MODULE input_cp2k_embed
13 : USE bibliography, ONLY: Heaton_Burgess2007,&
14 : Huang2011
15 : USE cp_output_handling, ONLY: add_last_numeric,&
16 : cp_print_key_section_create,&
17 : low_print_level
18 : USE input_constants, ONLY: dfet,&
19 : dmfet
20 : USE input_keyword_types, ONLY: keyword_create,&
21 : keyword_release,&
22 : keyword_type
23 : USE input_section_types, ONLY: section_add_keyword,&
24 : section_add_subsection,&
25 : section_create,&
26 : section_release,&
27 : section_type
28 : USE input_val_types, ONLY: integer_t
29 : USE string_utilities, ONLY: s2a
30 : #include "./base/base_uses.f90"
31 :
32 : IMPLICIT NONE
33 : PRIVATE
34 :
35 : LOGICAL, PRIVATE, PARAMETER :: debug_this_module = .TRUE.
36 : CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'input_cp2k_embed'
37 :
38 : PUBLIC :: create_embed_section
39 :
40 : CONTAINS
41 :
42 : ! **************************************************************************************************
43 : !> \brief Create the input section for EMBED: clone of the subroutines for MIXED
44 : !> \param section the section to create
45 : !> \author Vladimir Rybkin
46 : ! **************************************************************************************************
47 8530 : SUBROUTINE create_embed_section(section)
48 : TYPE(section_type), POINTER :: section
49 :
50 : TYPE(keyword_type), POINTER :: keyword
51 : TYPE(section_type), POINTER :: sub2section, sub3section, subsection
52 :
53 8530 : CPASSERT(.NOT. ASSOCIATED(section))
54 : CALL section_create(section, __LOCATION__, name="EMBED", &
55 : description="This section contains all information to run embedded "// &
56 : "calculations.", &
57 : n_keywords=1, n_subsections=0, repeats=.FALSE., &
58 25590 : citations=(/Huang2011, Heaton_Burgess2007/))
59 8530 : NULLIFY (keyword, subsection)
60 :
61 : CALL keyword_create(keyword, __LOCATION__, name="EMBED_METHOD", &
62 : description="Select DFET or DMFET.", &
63 : usage="EMBED_METHOD DFET", &
64 : default_i_val=dfet, &
65 : enum_c_vals=s2a("DFET", "DMFET"), &
66 : enum_desc=s2a("DFET", "DMFET"), &
67 8530 : enum_i_vals=(/dfet, dmfet/))
68 8530 : CALL section_add_keyword(section, keyword)
69 8530 : CALL keyword_release(keyword)
70 :
71 : ! Group partitioning
72 : CALL keyword_create(keyword, __LOCATION__, name="GROUP_PARTITION", &
73 : description="gives the exact number of processors for each group."// &
74 : " If not specified processors allocated will be equally distributed for"// &
75 : " the specified subforce_eval, trying to build a number of groups equal to the"// &
76 : " number of subforce_eval specified.", &
77 8530 : usage="group_partition 2 2 4 2 4 ", type_of_var=integer_t, n_var=-1)
78 8530 : CALL section_add_keyword(section, keyword)
79 8530 : CALL keyword_release(keyword)
80 :
81 : CALL keyword_create(keyword, __LOCATION__, name="NGROUPS", variants=(/"NGROUP"/), &
82 : description="Gives the wanted number of groups. Currently must be set to 1", &
83 17060 : usage="ngroups 4", type_of_var=integer_t, default_i_val=1)
84 8530 : CALL section_add_keyword(section, keyword)
85 8530 : CALL keyword_release(keyword)
86 :
87 : ! Mapping of atoms
88 8530 : NULLIFY (sub2section, sub3section)
89 : CALL section_create(subsection, __LOCATION__, name="MAPPING", &
90 : description="Defines the mapping of atoms for the different force_eval with the mixed force_eval."// &
91 : " The default is to have a mapping 1-1 between atom index (i.e. all force_eval share the same"// &
92 : " geometrical structure). The mapping is based on defining fragments and the mapping the"// &
93 : " fragments between the several force_eval and the mixed force_eval", &
94 8530 : n_keywords=1, n_subsections=0, repeats=.TRUE.)
95 :
96 : ! Mixed force_eval
97 : CALL section_create(sub2section, __LOCATION__, name="FORCE_EVAL_EMBED", &
98 : description="Defines the fragments for the embedding force_eval (reference)", &
99 8530 : n_keywords=1, n_subsections=0, repeats=.TRUE.)
100 :
101 : CALL section_create(sub3section, __LOCATION__, name="FRAGMENT", &
102 : description="Fragment definition", &
103 8530 : n_keywords=1, n_subsections=0, repeats=.TRUE.)
104 :
105 : CALL keyword_create(keyword, __LOCATION__, name="_SECTION_PARAMETERS_", &
106 : description="Defines the index of the fragment defined", &
107 8530 : usage="<INTEGER>", type_of_var=integer_t, n_var=1)
108 8530 : CALL section_add_keyword(sub3section, keyword)
109 8530 : CALL keyword_release(keyword)
110 :
111 : CALL keyword_create(keyword, __LOCATION__, name="_DEFAULT_KEYWORD_", &
112 : description="Starting and ending atomic index defining one fragment must be provided", &
113 8530 : usage="{Integer} {Integer}", type_of_var=integer_t, n_var=2, repeats=.TRUE.)
114 8530 : CALL section_add_keyword(sub3section, keyword)
115 8530 : CALL keyword_release(keyword)
116 :
117 8530 : CALL section_add_subsection(sub2section, sub3section)
118 8530 : CALL section_release(sub3section)
119 8530 : CALL section_add_subsection(subsection, sub2section)
120 8530 : CALL section_release(sub2section)
121 :
122 : ! All other force_eval
123 : CALL section_create(sub2section, __LOCATION__, name="FORCE_EVAL", &
124 : description="Defines the fragments and the mapping for each force_eval (an integer index (ID) "// &
125 : "needs to be provided as parameter)", &
126 8530 : n_keywords=1, n_subsections=0, repeats=.TRUE.)
127 :
128 : CALL keyword_create( &
129 : keyword, __LOCATION__, name="DEFINE_FRAGMENTS", &
130 : description="Specify the fragments definition of the force_eval through the fragments of the"// &
131 : " force_eval_embed. This avoids the pedantic definition of the fragments for the force_eval,"// &
132 : " assuming the order of the fragments for the specified force_eval is the same as the sequence"// &
133 : " of integers provided. Easier to USE should be preferred to the specification of the single fragments.", &
134 8530 : usage="DEFINE_FRAGMENTS <INTEGER> .. <INTEGER>", type_of_var=integer_t, n_var=-1)
135 8530 : CALL section_add_keyword(sub2section, keyword)
136 8530 : CALL keyword_release(keyword)
137 :
138 : CALL keyword_create(keyword, __LOCATION__, name="_SECTION_PARAMETERS_", &
139 : description="Defines the index of the force_eval for which fragments and mappings are provided", &
140 8530 : usage="<INTEGER>", type_of_var=integer_t, n_var=1)
141 8530 : CALL section_add_keyword(sub2section, keyword)
142 8530 : CALL keyword_release(keyword)
143 :
144 : CALL section_create(sub3section, __LOCATION__, name="FRAGMENT", &
145 : description="Fragment definition", &
146 8530 : n_keywords=1, n_subsections=0, repeats=.TRUE.)
147 :
148 : CALL keyword_create(keyword, __LOCATION__, name="_SECTION_PARAMETERS_", &
149 : description="Defines the index of the fragment defined", &
150 8530 : usage="<INTEGER>", type_of_var=integer_t, n_var=1)
151 8530 : CALL section_add_keyword(sub3section, keyword)
152 8530 : CALL keyword_release(keyword)
153 :
154 : CALL keyword_create(keyword, __LOCATION__, name="_DEFAULT_KEYWORD_", &
155 : description="Starting and ending atomic index defining one fragment must be provided", &
156 8530 : usage="{Integer} {Integer}", type_of_var=integer_t, n_var=2, repeats=.FALSE.)
157 8530 : CALL section_add_keyword(sub3section, keyword)
158 8530 : CALL keyword_release(keyword)
159 :
160 : CALL keyword_create(keyword, __LOCATION__, name="MAP", &
161 : description="Provides the index of the fragment of the MIXED force_eval mapped on the"// &
162 : " locally defined fragment.", &
163 8530 : usage="MAP <INTEGER>", type_of_var=integer_t, n_var=1, repeats=.FALSE.)
164 8530 : CALL section_add_keyword(sub3section, keyword)
165 8530 : CALL keyword_release(keyword)
166 :
167 8530 : CALL section_add_subsection(sub2section, sub3section)
168 8530 : CALL section_release(sub3section)
169 8530 : CALL section_add_subsection(subsection, sub2section)
170 8530 : CALL section_release(sub2section)
171 :
172 8530 : CALL section_add_subsection(section, subsection)
173 8530 : CALL section_release(subsection)
174 :
175 8530 : CALL create_print_embed_section(subsection)
176 8530 : CALL section_add_subsection(section, subsection)
177 8530 : CALL section_release(subsection)
178 8530 : END SUBROUTINE create_embed_section
179 :
180 : ! **************************************************************************************************
181 : !> \brief Create the print section for embedding
182 : !> \param section the section to create
183 : !> \author Vladimir Rybkin
184 : ! **************************************************************************************************
185 8530 : SUBROUTINE create_print_embed_section(section)
186 : TYPE(section_type), POINTER :: section
187 :
188 : TYPE(section_type), POINTER :: print_key
189 :
190 8530 : CPASSERT(.NOT. ASSOCIATED(section))
191 : CALL section_create(section, __LOCATION__, name="print", &
192 : description="Section of possible print options in EMBED env.", &
193 8530 : n_keywords=0, n_subsections=1, repeats=.FALSE.)
194 :
195 8530 : NULLIFY (print_key)
196 :
197 : CALL cp_print_key_section_create(print_key, __LOCATION__, "PROGRAM_RUN_INFO", &
198 : description="Controls the printing of information during the evaluation of "// &
199 : "the embedding environment. ", &
200 8530 : print_level=low_print_level, add_last=add_last_numeric, filename="__STD_OUT__")
201 8530 : CALL section_add_subsection(section, print_key)
202 8530 : CALL section_release(print_key)
203 :
204 8530 : END SUBROUTINE create_print_embed_section
205 :
206 : END MODULE input_cp2k_embed
|