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 initialize embed environment: clone of the mixed environment
10 : !> \author Vladimir Rybkin
11 : ! **************************************************************************************************
12 : MODULE embed_environment
13 : USE atomic_kind_types, ONLY: atomic_kind_type
14 : USE cell_methods, ONLY: read_cell,&
15 : write_cell
16 : USE cell_types, ONLY: cell_release,&
17 : cell_type,&
18 : get_cell
19 : USE cp_subsys_methods, ONLY: cp_subsys_create
20 : USE cp_subsys_types, ONLY: cp_subsys_set,&
21 : cp_subsys_type
22 : USE distribution_1d_types, ONLY: distribution_1d_release,&
23 : distribution_1d_type
24 : USE distribution_methods, ONLY: distribute_molecules_1d
25 : USE embed_types, ONLY: embed_env_type,&
26 : set_embed_env
27 : USE input_section_types, ONLY: section_vals_get_subs_vals,&
28 : section_vals_type
29 : USE kinds, ONLY: dp
30 : USE message_passing, ONLY: mp_para_env_type
31 : USE molecule_kind_types, ONLY: molecule_kind_type,&
32 : write_molecule_kind_set
33 : USE molecule_types, ONLY: molecule_type
34 : USE particle_types, ONLY: particle_type
35 : #include "./base/base_uses.f90"
36 :
37 : IMPLICIT NONE
38 :
39 : PRIVATE
40 :
41 : CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'embed_environment'
42 : PUBLIC :: embed_init
43 :
44 : CONTAINS
45 :
46 : ! **************************************************************************************************
47 : !> \brief reads the input and database file for embedding
48 : !> \param embed_env ...
49 : !> \param root_section ...
50 : !> \param para_env ...
51 : !> \param force_env_section ...
52 : !> \param use_motion_section ...
53 : !> \par Used By
54 : !> embed_main
55 : !> \author Vladimir Rybkin
56 : ! **************************************************************************************************
57 24 : SUBROUTINE embed_init(embed_env, root_section, para_env, force_env_section, &
58 : use_motion_section)
59 :
60 : TYPE(embed_env_type), INTENT(INOUT) :: embed_env
61 : TYPE(section_vals_type), POINTER :: root_section
62 : TYPE(mp_para_env_type), POINTER :: para_env
63 : TYPE(section_vals_type), POINTER :: force_env_section
64 : LOGICAL, INTENT(IN) :: use_motion_section
65 :
66 : CHARACTER(len=*), PARAMETER :: routineN = 'embed_init'
67 :
68 : INTEGER :: handle
69 : LOGICAL :: use_ref_cell
70 : REAL(KIND=dp), DIMENSION(3) :: abc
71 : TYPE(cell_type), POINTER :: cell, cell_ref
72 : TYPE(cp_subsys_type), POINTER :: subsys
73 : TYPE(section_vals_type), POINTER :: cell_section, subsys_section
74 :
75 24 : CALL timeset(routineN, handle)
76 :
77 24 : NULLIFY (subsys, cell, cell_ref)
78 24 : NULLIFY (cell_section)
79 :
80 24 : subsys_section => section_vals_get_subs_vals(force_env_section, "SUBSYS")
81 24 : cell_section => section_vals_get_subs_vals(subsys_section, "CELL")
82 :
83 24 : CALL set_embed_env(embed_env, input=force_env_section)
84 : CALL cp_subsys_create(subsys, para_env, root_section, &
85 : force_env_section=force_env_section, &
86 24 : use_motion_section=use_motion_section)
87 :
88 : CALL read_cell(cell, cell_ref, use_ref_cell=use_ref_cell, &
89 24 : cell_section=cell_section, para_env=para_env)
90 24 : CALL get_cell(cell, abc=abc)
91 :
92 : ! Print the cell parameters ***
93 24 : CALL write_cell(cell, subsys_section)
94 24 : CALL write_cell(cell_ref, subsys_section)
95 :
96 : CALL embed_init_subsys(embed_env, subsys, cell, cell_ref, &
97 24 : force_env_section, subsys_section)
98 :
99 24 : CALL cell_release(cell)
100 24 : CALL cell_release(cell_ref)
101 :
102 24 : CALL timestop(handle)
103 :
104 24 : END SUBROUTINE embed_init
105 :
106 : ! **************************************************************************************************
107 : !> \brief Read the input and the database files for the setup of the
108 : !> embed environment.
109 : !> \param embed_env ...
110 : !> \param subsys ...
111 : !> \param cell ...
112 : !> \param cell_ref ...
113 : !> \param force_env_section ...
114 : !> \param subsys_section ...
115 : !> \date 02.2018
116 : !> \author Vladimir Rybkin
117 : ! **************************************************************************************************
118 24 : SUBROUTINE embed_init_subsys(embed_env, subsys, cell, cell_ref, &
119 : force_env_section, subsys_section)
120 :
121 : TYPE(embed_env_type), INTENT(INOUT) :: embed_env
122 : TYPE(cp_subsys_type), POINTER :: subsys
123 : TYPE(cell_type), POINTER :: cell, cell_ref
124 : TYPE(section_vals_type), POINTER :: force_env_section, subsys_section
125 :
126 : CHARACTER(len=*), PARAMETER :: routineN = 'embed_init_subsys'
127 :
128 : INTEGER :: handle
129 24 : TYPE(atomic_kind_type), DIMENSION(:), POINTER :: atomic_kind_set
130 : TYPE(distribution_1d_type), POINTER :: local_molecules, local_particles
131 24 : TYPE(molecule_kind_type), DIMENSION(:), POINTER :: molecule_kind_set
132 24 : TYPE(molecule_type), DIMENSION(:), POINTER :: molecule_set
133 24 : TYPE(particle_type), DIMENSION(:), POINTER :: particle_set
134 :
135 24 : CALL timeset(routineN, handle)
136 24 : NULLIFY (local_molecules, local_particles)
137 24 : particle_set => subsys%particles%els
138 24 : atomic_kind_set => subsys%atomic_kinds%els
139 24 : molecule_set => subsys%molecules%els
140 24 : molecule_kind_set => subsys%molecule_kinds%els
141 :
142 : ! Print the molecule kind set
143 24 : CALL write_molecule_kind_set(molecule_kind_set, subsys_section)
144 :
145 : ! Distribute molecules and atoms using the new data structures ***
146 : CALL distribute_molecules_1d(atomic_kind_set=atomic_kind_set, &
147 : particle_set=particle_set, &
148 : local_particles=local_particles, &
149 : molecule_kind_set=molecule_kind_set, &
150 : molecule_set=molecule_set, &
151 : local_molecules=local_molecules, &
152 24 : force_env_section=force_env_section)
153 :
154 24 : CALL cp_subsys_set(subsys, cell=cell)
155 :
156 : ! set the embed_env
157 24 : CALL set_embed_env(embed_env=embed_env, subsys=subsys)
158 : CALL set_embed_env(embed_env=embed_env, &
159 : cell_ref=cell_ref, &
160 : local_molecules=local_molecules, &
161 24 : local_particles=local_particles)
162 :
163 24 : CALL distribution_1d_release(local_particles)
164 24 : CALL distribution_1d_release(local_molecules)
165 :
166 24 : CALL timestop(handle)
167 :
168 24 : END SUBROUTINE embed_init_subsys
169 :
170 : END MODULE embed_environment
|