(git:374b731)
Loading...
Searching...
No Matches
input_cp2k_embed.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!> \brief builds the input structure for the EMBED environment: clone of MIXED environment
10!> \author Vladimir Rybkin - University of Zurich
11! **************************************************************************************************
18 USE input_constants, ONLY: dfet,&
19 dmfet
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
40CONTAINS
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 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 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 citations=(/huang2011, heaton_burgess2007/))
59 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 enum_i_vals=(/dfet, dmfet/))
68 CALL section_add_keyword(section, keyword)
69 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 usage="group_partition 2 2 4 2 4 ", type_of_var=integer_t, n_var=-1)
78 CALL section_add_keyword(section, keyword)
79 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 usage="ngroups 4", type_of_var=integer_t, default_i_val=1)
84 CALL section_add_keyword(section, keyword)
85 CALL keyword_release(keyword)
86
87 ! Mapping of atoms
88 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 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 n_keywords=1, n_subsections=0, repeats=.true.)
100
101 CALL section_create(sub3section, __location__, name="FRAGMENT", &
102 description="Fragment definition", &
103 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 usage="<INTEGER>", type_of_var=integer_t, n_var=1)
108 CALL section_add_keyword(sub3section, keyword)
109 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 usage="{Integer} {Integer}", type_of_var=integer_t, n_var=2, repeats=.true.)
114 CALL section_add_keyword(sub3section, keyword)
115 CALL keyword_release(keyword)
116
117 CALL section_add_subsection(sub2section, sub3section)
118 CALL section_release(sub3section)
119 CALL section_add_subsection(subsection, sub2section)
120 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 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 usage="DEFINE_FRAGMENTS <INTEGER> .. <INTEGER>", type_of_var=integer_t, n_var=-1)
135 CALL section_add_keyword(sub2section, keyword)
136 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 usage="<INTEGER>", type_of_var=integer_t, n_var=1)
141 CALL section_add_keyword(sub2section, keyword)
142 CALL keyword_release(keyword)
143
144 CALL section_create(sub3section, __location__, name="FRAGMENT", &
145 description="Fragment definition", &
146 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 usage="<INTEGER>", type_of_var=integer_t, n_var=1)
151 CALL section_add_keyword(sub3section, keyword)
152 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 usage="{Integer} {Integer}", type_of_var=integer_t, n_var=2, repeats=.false.)
157 CALL section_add_keyword(sub3section, keyword)
158 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 usage="MAP <INTEGER>", type_of_var=integer_t, n_var=1, repeats=.false.)
164 CALL section_add_keyword(sub3section, keyword)
165 CALL keyword_release(keyword)
166
167 CALL section_add_subsection(sub2section, sub3section)
168 CALL section_release(sub3section)
169 CALL section_add_subsection(subsection, sub2section)
170 CALL section_release(sub2section)
171
172 CALL section_add_subsection(section, subsection)
173 CALL section_release(subsection)
174
175 CALL create_print_embed_section(subsection)
176 CALL section_add_subsection(section, subsection)
177 CALL section_release(subsection)
178 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 SUBROUTINE create_print_embed_section(section)
186 TYPE(section_type), POINTER :: section
187
188 TYPE(section_type), POINTER :: print_key
189
190 cpassert(.NOT. ASSOCIATED(section))
191 CALL section_create(section, __location__, name="print", &
192 description="Section of possible print options in EMBED env.", &
193 n_keywords=0, n_subsections=1, repeats=.false.)
194
195 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 print_level=low_print_level, add_last=add_last_numeric, filename="__STD_OUT__")
201 CALL section_add_subsection(section, print_key)
202 CALL section_release(print_key)
203
204 END SUBROUTINE create_print_embed_section
205
206END MODULE input_cp2k_embed
collects all references to literature in CP2K as new algorithms / method are included from literature...
integer, save, public huang2011
integer, save, public heaton_burgess2007
routines to handle the output, The idea is to remove the decision of wheter to output and what to out...
integer, parameter, public low_print_level
integer, parameter, public add_last_numeric
subroutine, public cp_print_key_section_create(print_key_section, location, name, description, print_level, each_iter_names, each_iter_values, add_last, filename, common_iter_levels, citations, unit_str)
creates a print_key section
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public dmfet
integer, parameter, public dfet
builds the input structure for the EMBED environment: clone of MIXED environment
subroutine, public create_embed_section(section)
Create the input section for EMBED: clone of the subroutines for MIXED.
represents keywords in an input
subroutine, public keyword_release(keyword)
releases the given keyword (see doc/ReferenceCounting.html)
subroutine, public keyword_create(keyword, location, name, description, usage, type_of_var, n_var, repeats, variants, default_val, default_l_val, default_r_val, default_lc_val, default_c_val, default_i_val, default_l_vals, default_r_vals, default_c_vals, default_i_vals, lone_keyword_val, lone_keyword_l_val, lone_keyword_r_val, lone_keyword_c_val, lone_keyword_i_val, lone_keyword_l_vals, lone_keyword_r_vals, lone_keyword_c_vals, lone_keyword_i_vals, enum_c_vals, enum_i_vals, enum, enum_strict, enum_desc, unit_str, citations, deprecation_notice, removed)
creates a keyword object
objects that represent the structure of input sections and the data contained in an input section
subroutine, public section_create(section, location, name, description, n_keywords, n_subsections, repeats, citations)
creates a list of keywords
subroutine, public section_add_keyword(section, keyword)
adds a keyword to the given section
subroutine, public section_add_subsection(section, subsection)
adds a subsection to the given section
recursive subroutine, public section_release(section)
releases the given keyword list (see doc/ReferenceCounting.html)
a wrapper for basic fortran types.
integer, parameter, public integer_t
Utilities for string manipulations.
represent a keyword in the input
represent a section of the input file