(git:374b731)
Loading...
Searching...
No Matches
embed_environment.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 initialize embed environment: clone of the mixed environment
10!> \author Vladimir Rybkin
11! **************************************************************************************************
14 USE cell_methods, ONLY: read_cell,&
16 USE cell_types, ONLY: cell_release,&
17 cell_type,&
25 USE embed_types, ONLY: embed_env_type,&
29 USE kinds, ONLY: dp
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
44CONTAINS
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 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 CALL timeset(routinen, handle)
76
77 NULLIFY (subsys, cell, cell_ref)
78 NULLIFY (cell_section)
79
80 subsys_section => section_vals_get_subs_vals(force_env_section, "SUBSYS")
81 cell_section => section_vals_get_subs_vals(subsys_section, "CELL")
82
83 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 use_motion_section=use_motion_section)
87
88 CALL read_cell(cell, cell_ref, use_ref_cell=use_ref_cell, &
89 cell_section=cell_section, para_env=para_env)
90 CALL get_cell(cell, abc=abc)
91
92 ! Print the cell parameters ***
93 CALL write_cell(cell, subsys_section)
94 CALL write_cell(cell_ref, subsys_section)
95
96 CALL embed_init_subsys(embed_env, subsys, cell, cell_ref, &
97 force_env_section, subsys_section)
98
99 CALL cell_release(cell)
100 CALL cell_release(cell_ref)
101
102 CALL timestop(handle)
103
104 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 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 TYPE(atomic_kind_type), DIMENSION(:), POINTER :: atomic_kind_set
130 TYPE(distribution_1d_type), POINTER :: local_molecules, local_particles
131 TYPE(molecule_kind_type), DIMENSION(:), POINTER :: molecule_kind_set
132 TYPE(molecule_type), DIMENSION(:), POINTER :: molecule_set
133 TYPE(particle_type), DIMENSION(:), POINTER :: particle_set
134
135 CALL timeset(routinen, handle)
136 NULLIFY (local_molecules, local_particles)
137 particle_set => subsys%particles%els
138 atomic_kind_set => subsys%atomic_kinds%els
139 molecule_set => subsys%molecules%els
140 molecule_kind_set => subsys%molecule_kinds%els
141
142 ! Print the molecule kind set
143 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 force_env_section=force_env_section)
153
154 CALL cp_subsys_set(subsys, cell=cell)
155
156 ! set the embed_env
157 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 local_particles=local_particles)
162
163 CALL distribution_1d_release(local_particles)
164 CALL distribution_1d_release(local_molecules)
165
166 CALL timestop(handle)
167
168 END SUBROUTINE embed_init_subsys
169
170END MODULE embed_environment
Define the atomic kind types and their sub types.
Handles all functions related to the CELL.
recursive subroutine, public read_cell(cell, cell_ref, use_ref_cell, cell_section, check_for_ref, para_env)
...
subroutine, public write_cell(cell, subsys_section, tag)
Write the cell parameters to the output unit.
Handles all functions related to the CELL.
Definition cell_types.F:15
subroutine, public cell_release(cell)
releases the given cell (see doc/ReferenceCounting.html)
Definition cell_types.F:559
subroutine, public get_cell(cell, alpha, beta, gamma, deth, orthorhombic, abc, periodic, h, h_inv, symmetry_id, tag)
Get informations about a simulation cell.
Definition cell_types.F:195
Initialize a small environment for a particular calculation.
subroutine, public cp_subsys_create(subsys, para_env, root_section, force_env_section, subsys_section, use_motion_section, qmmm, qmmm_env, exclusions, elkind)
Creates allocates and fills subsys from given input.
types that represent a subsys, i.e. a part of the system
subroutine, public cp_subsys_set(subsys, atomic_kinds, particles, local_particles, molecules, molecule_kinds, local_molecules, para_env, colvar_p, shell_particles, core_particles, gci, multipoles, results, cell)
sets various propreties of the subsys
stores a lists of integer that are local to a processor. The idea is that these integers represent ob...
subroutine, public distribution_1d_release(distribution_1d)
releases the given distribution_1d
Distribution methods for atoms, particles, or molecules.
subroutine, public distribute_molecules_1d(atomic_kind_set, particle_set, local_particles, molecule_kind_set, molecule_set, local_molecules, force_env_section, prev_molecule_kind_set, prev_local_molecules)
Distribute molecules and particles.
initialize embed environment: clone of the mixed environment
subroutine, public embed_init(embed_env, root_section, para_env, force_env_section, use_motion_section)
reads the input and database file for embedding
subroutine, public set_embed_env(embed_env, atomic_kind_set, particle_set, local_particles, local_molecules, molecule_kind_set, molecule_set, cell_ref, subsys, input, sub_para_env)
...
objects that represent the structure of input sections and the data contained in an input section
recursive type(section_vals_type) function, pointer, public section_vals_get_subs_vals(section_vals, subsection_name, i_rep_section, can_return_null)
returns the values of the requested subsection
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
Interface to the message passing library MPI.
Define the molecule kind structure types and the corresponding functionality.
subroutine, public write_molecule_kind_set(molecule_kind_set, subsys_section)
Write a moleculeatomic kind set data set to the output unit.
Define the data structure for the molecule information.
Define the data structure for the particle information.
Provides all information about an atomic kind.
Type defining parameters related to the simulation cell.
Definition cell_types.F:55
represents a system: atoms, molecules, their pos,vel,...
structure to store local (to a processor) ordered lists of integers.
Embedding environment type.
stores all the informations relevant to an mpi environment