41#include "./base/base_uses.f90"
49 CHARACTER(len=*),
PARAMETER,
PRIVATE :: moduleN =
'ipi_environment'
68 SUBROUTINE ipi_init(ipi_env, root_section, para_env, force_env_section, &
75 CHARACTER(len=*),
PARAMETER :: routinen =
'ipi_init'
78 REAL(kind=
dp),
DIMENSION(3) :: abc
79 TYPE(
cell_type),
POINTER :: cell, cell_ref
84 CALL timeset(routinen, handle)
86 cpassert(
ASSOCIATED(ipi_env))
89 NULLIFY (cell_section, cell, cell_ref, subsys)
91 IF (.NOT.
ASSOCIATED(subsys_section))
THEN
96 CALL ipi_env_set(ipi_env=ipi_env, force_env_input=force_env_section)
98 CALL read_cell(cell=cell, cell_ref=cell_ref, &
99 cell_section=cell_section, para_env=para_env)
101 CALL write_cell(cell=cell, subsys_section=subsys_section)
105 CALL ipi_init_subsys(ipi_env=ipi_env, subsys=subsys, cell=cell, &
106 cell_ref=cell_ref, subsys_section=subsys_section)
113 CALL start_server(para_env=para_env, driver_section=driver_section, ipi_env=ipi_env)
115 CALL timestop(handle)
130 SUBROUTINE ipi_init_subsys(ipi_env, subsys, cell, cell_ref, subsys_section)
133 TYPE(
cell_type),
POINTER :: cell, cell_ref
136 CHARACTER(len=*),
PARAMETER :: routinen =
'ipi_init_subsys'
138 INTEGER :: handle, natom
145 CALL timeset(routinen, handle)
147 NULLIFY (atomic_kind_set, molecule_kind_set, particle_set, molecule_set, &
148 local_molecules, local_particles)
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
161 subsys_section=subsys_section)
163 input_section=subsys_section)
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)
174 natom =
SIZE(particle_set)
176 ALLOCATE (ipi_env%ipi_forces(3, natom))
177 ipi_env%ipi_forces(:, :) = 0.0_dp
182 local_molecules=local_molecules, &
183 local_particles=local_particles)
188 CALL timestop(handle)
190 END SUBROUTINE ipi_init_subsys
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.
subroutine, public cell_release(cell)
releases the given cell (see doc/ReferenceCounting.html)
subroutine, public get_cell(cell, alpha, beta, gamma, deth, orthorhombic, abc, periodic, h, h_inv, symmetry_id, tag)
Get informations about a simulation cell.
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.
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
subroutine, public start_server(driver_section, para_env, ipi_env)
Starts the i–PI server. Will block until it recieves a connection.
Defines the basic variable types.
integer, parameter, public dp
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.
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