(git:ed6f26b)
Loading...
Searching...
No Matches
ipi_environment.F
Go to the documentation of this file.
1!--------------------------------------------------------------------------------------------------!
2! CP2K: A general program to perform molecular dynamics simulations !
3! Copyright 2000-2025 CP2K developers group <https://cp2k.org> !
4! !
5! SPDX-License-Identifier: GPL-2.0-or-later !
6!--------------------------------------------------------------------------------------------------!
7
8! **************************************************************************************************
9!> \brief Methods and functions on the i–PI environment
10!> \par History
11!> 03.2024 initial create
12!> \author Sebastian Seidenath (sebastian.seidenath@uni-jena.de)
13! **************************************************************************************************
16 USE cell_methods, ONLY: read_cell,&
18 USE cell_types, ONLY: cell_release,&
19 cell_type,&
31 USE ipi_server, ONLY: start_server
32 USE kinds, ONLY: dp
41#include "./base/base_uses.f90"
42
43 IMPLICIT NONE
44
45 PRIVATE
46
47! *** Global parameters ***
48
49 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'ipi_environment'
50
51! *** Public subroutines ***
52
53 PUBLIC :: ipi_init
54
55CONTAINS
56
57! **************************************************************************************************
58!> \brief Initialize the ipi environment
59!> \param ipi_env The ipi environment to retain
60!> \param root_section ...
61!> \param para_env ...
62!> \param force_env_section ...
63!> \param subsys_section ...
64!> \par History
65!> 03.2006 initial create
66!> \author Sebastian Seidenath (sebastian.seidenath@uni-jena.de)
67! **************************************************************************************************
68 SUBROUTINE ipi_init(ipi_env, root_section, para_env, force_env_section, &
69 subsys_section)
70 TYPE(ipi_environment_type), POINTER :: ipi_env
71 TYPE(section_vals_type), POINTER :: root_section
72 TYPE(mp_para_env_type), POINTER :: para_env
73 TYPE(section_vals_type), POINTER :: force_env_section, subsys_section
74
75 CHARACTER(len=*), PARAMETER :: routinen = 'ipi_init'
76
77 INTEGER :: handle
78 REAL(kind=dp), DIMENSION(3) :: abc
79 TYPE(cell_type), POINTER :: cell, cell_ref
80 TYPE(cp_subsys_type), POINTER :: subsys
81 TYPE(section_vals_type), POINTER :: cell_section, driver_section, &
82 motion_section
83
84 CALL timeset(routinen, handle)
85
86 cpassert(ASSOCIATED(ipi_env))
87
88 ! nullifying pointers
89 NULLIFY (cell_section, cell, cell_ref, subsys)
90
91 IF (.NOT. ASSOCIATED(subsys_section)) THEN
92 subsys_section => section_vals_get_subs_vals(force_env_section, "SUBSYS")
93 END IF
94 cell_section => section_vals_get_subs_vals(subsys_section, "CELL")
95
96 CALL ipi_env_set(ipi_env=ipi_env, force_env_input=force_env_section)
97
98 CALL read_cell(cell=cell, cell_ref=cell_ref, &
99 cell_section=cell_section, para_env=para_env)
100 CALL get_cell(cell=cell, abc=abc)
101 CALL write_cell(cell=cell, subsys_section=subsys_section)
102
103 CALL cp_subsys_create(subsys, para_env, root_section)
104
105 CALL ipi_init_subsys(ipi_env=ipi_env, subsys=subsys, cell=cell, &
106 cell_ref=cell_ref, subsys_section=subsys_section)
107
108 CALL cell_release(cell)
109 CALL cell_release(cell_ref)
110
111 motion_section => section_vals_get_subs_vals(root_section, "MOTION")
112 driver_section => section_vals_get_subs_vals(motion_section, "DRIVER")
113 CALL start_server(para_env=para_env, driver_section=driver_section, ipi_env=ipi_env)
114
115 CALL timestop(handle)
116
117 END SUBROUTINE ipi_init
118
119! **************************************************************************************************
120!> \brief Initialize the ipi environment
121!> \param ipi_env The ipi environment
122!> \param subsys the subsys
123!> \param cell Pointer to the actual simulation cell
124!> \param cell_ref Pointer to the reference cell, used e.g. in NPT simulations
125!> \param subsys_section ...
126!> \par History
127!> 03.2024 initial create
128!> \author Sebastian Seidenath (sebastian.seidenath@uni-jena.de)
129! **************************************************************************************************
130 SUBROUTINE ipi_init_subsys(ipi_env, subsys, cell, cell_ref, subsys_section)
131 TYPE(ipi_environment_type), POINTER :: ipi_env
132 TYPE(cp_subsys_type), POINTER :: subsys
133 TYPE(cell_type), POINTER :: cell, cell_ref
134 TYPE(section_vals_type), POINTER :: subsys_section
135
136 CHARACTER(len=*), PARAMETER :: routinen = 'ipi_init_subsys'
137
138 INTEGER :: handle, natom
139 TYPE(atomic_kind_type), DIMENSION(:), POINTER :: atomic_kind_set
140 TYPE(distribution_1d_type), POINTER :: local_molecules, local_particles
141 TYPE(molecule_kind_type), DIMENSION(:), POINTER :: molecule_kind_set
142 TYPE(molecule_type), DIMENSION(:), POINTER :: molecule_set
143 TYPE(particle_type), DIMENSION(:), POINTER :: particle_set
144
145 CALL timeset(routinen, handle)
146
147 NULLIFY (atomic_kind_set, molecule_kind_set, particle_set, molecule_set, &
148 local_molecules, local_particles)
149
150 particle_set => subsys%particles%els
151 atomic_kind_set => subsys%atomic_kinds%els
152 molecule_kind_set => subsys%molecule_kinds%els
153 molecule_set => subsys%molecules%els
154
155! *** Print the molecule kind set ***
156 CALL write_molecule_kind_set(molecule_kind_set, subsys_section)
157
158! *** Print the atomic coordinates ***
159 CALL write_fist_particle_coordinates(particle_set, subsys_section)
160 CALL write_particle_distances(particle_set, cell=cell, &
161 subsys_section=subsys_section)
162 CALL write_structure_data(particle_set, cell=cell, &
163 input_section=subsys_section)
164
165! *** Distribute molecules and atoms using the new data structures ***
166 CALL distribute_molecules_1d(atomic_kind_set=atomic_kind_set, &
167 particle_set=particle_set, &
168 local_particles=local_particles, &
169 molecule_kind_set=molecule_kind_set, &
170 molecule_set=molecule_set, &
171 local_molecules=local_molecules, &
172 force_env_section=ipi_env%force_env_input)
173
174 natom = SIZE(particle_set)
175
176 ALLOCATE (ipi_env%ipi_forces(3, natom))
177 ipi_env%ipi_forces(:, :) = 0.0_dp
178
179 CALL cp_subsys_set(subsys, cell=cell)
180 CALL ipi_env_set(ipi_env=ipi_env, subsys=subsys, &
181 cell_ref=cell_ref, &
182 local_molecules=local_molecules, &
183 local_particles=local_particles)
184
185 CALL distribution_1d_release(local_particles)
186 CALL distribution_1d_release(local_molecules)
187
188 CALL timestop(handle)
189
190 END SUBROUTINE ipi_init_subsys
191
192END MODULE ipi_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.
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
The environment for the empirical interatomic potential methods.
subroutine, public ipi_env_set(ipi_env, ipi_energy, ipi_forces, subsys, atomic_kind_set, particle_set, local_particles, molecule_kind_set, molecule_set, local_molecules, force_env_input, cell_ref, sockfd)
Sets various attributes of the ipi environment.
Methods and functions on the i–PI environment.
subroutine, public ipi_init(ipi_env, root_section, para_env, force_env_section, subsys_section)
Initialize the ipi environment.
i–PI server mode: Communication with i–PI clients
Definition ipi_server.F:14
subroutine, public start_server(driver_section, para_env, ipi_env)
Starts the i–PI server. Will block until it recieves a connection.
Definition ipi_server.F:79
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 methods related to particle_type.
subroutine, public write_fist_particle_coordinates(particle_set, subsys_section, charges)
Write the atomic coordinates to the output unit.
subroutine, public write_structure_data(particle_set, cell, input_section)
Write structure data requested by a separate structure data input section to the output unit....
subroutine, public write_particle_distances(particle_set, cell, subsys_section)
Write the matrix of the particle distances to the output unit.
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.
stores all the informations relevant to an mpi environment