(git:374b731)
Loading...
Searching...
No Matches
mixed_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 mixed environment
10!> \author fschiff
11! **************************************************************************************************
14 USE cell_methods, ONLY: read_cell,&
16 USE cell_types, ONLY: cell_release,&
17 cell_type,&
27 USE kinds, ONLY: dp
37#include "./base/base_uses.f90"
38
39 IMPLICIT NONE
40
41 PRIVATE
42
43 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'mixed_environment'
44 PUBLIC :: mixed_init
45
46CONTAINS
47
48! **************************************************************************************************
49!> \brief reads the input and database file for mixed
50!> \param mixed_env ...
51!> \param root_section ...
52!> \param para_env ...
53!> \param force_env_section ...
54!> \param use_motion_section ...
55!> \par Used By
56!> mixed_main
57!> \author fschiff
58! **************************************************************************************************
59 SUBROUTINE mixed_init(mixed_env, root_section, para_env, force_env_section, &
60 use_motion_section)
61
62 TYPE(mixed_environment_type), INTENT(INOUT) :: mixed_env
63 TYPE(section_vals_type), POINTER :: root_section
64 TYPE(mp_para_env_type), POINTER :: para_env
65 TYPE(section_vals_type), POINTER :: force_env_section
66 LOGICAL, INTENT(IN) :: use_motion_section
67
68 CHARACTER(len=*), PARAMETER :: routinen = 'mixed_init'
69
70 INTEGER :: handle
71 LOGICAL :: use_ref_cell
72 REAL(kind=dp), DIMENSION(3) :: abc
73 TYPE(cell_type), POINTER :: cell, cell_ref
74 TYPE(cp_subsys_type), POINTER :: subsys
75 TYPE(section_vals_type), POINTER :: cell_section, subsys_section
76
77 CALL timeset(routinen, handle)
78
79 NULLIFY (subsys, cell, cell_ref)
80 NULLIFY (cell_section)
81
82 subsys_section => section_vals_get_subs_vals(force_env_section, "SUBSYS")
83 cell_section => section_vals_get_subs_vals(subsys_section, "CELL")
84
85 CALL set_mixed_env(mixed_env, input=force_env_section)
86 CALL cp_subsys_create(subsys, para_env, root_section, &
87 force_env_section=force_env_section, &
88 use_motion_section=use_motion_section)
89
90 CALL read_cell(cell, cell_ref, use_ref_cell=use_ref_cell, &
91 cell_section=cell_section, para_env=para_env)
92 CALL get_cell(cell, abc=abc)
93
94 ! Print the cell parameters ***
95 CALL write_cell(cell, subsys_section)
96 CALL write_cell(cell_ref, subsys_section)
97
98 CALL mixed_init_subsys(mixed_env, subsys, cell, cell_ref, &
99 force_env_section, subsys_section)
100
101 CALL cell_release(cell)
102 CALL cell_release(cell_ref)
103
104 CALL timestop(handle)
105
106 END SUBROUTINE mixed_init
107
108! **************************************************************************************************
109!> \brief Read the input and the database files for the setup of the
110!> mixed environment.
111!> \param mixed_env ...
112!> \param subsys ...
113!> \param cell ...
114!> \param cell_ref ...
115!> \param force_env_section ...
116!> \param subsys_section ...
117!> \date 11.06
118!> \author fschiff
119!> \version 1.0
120! **************************************************************************************************
121 SUBROUTINE mixed_init_subsys(mixed_env, subsys, cell, cell_ref, &
122 force_env_section, subsys_section)
123
124 TYPE(mixed_environment_type), INTENT(INOUT) :: mixed_env
125 TYPE(cp_subsys_type), POINTER :: subsys
126 TYPE(cell_type), POINTER :: cell, cell_ref
127 TYPE(section_vals_type), POINTER :: force_env_section, subsys_section
128
129 CHARACTER(len=*), PARAMETER :: routinen = 'mixed_init_subsys'
130
131 INTEGER :: handle
132 TYPE(atomic_kind_type), DIMENSION(:), POINTER :: atomic_kind_set
133 TYPE(distribution_1d_type), POINTER :: local_molecules, local_particles
134 TYPE(mixed_energy_type), POINTER :: mixed_energy
135 TYPE(molecule_kind_type), DIMENSION(:), POINTER :: molecule_kind_set
136 TYPE(molecule_type), DIMENSION(:), POINTER :: molecule_set
137 TYPE(particle_type), DIMENSION(:), POINTER :: particle_set
138
139 CALL timeset(routinen, handle)
140 NULLIFY (mixed_energy, local_molecules, local_particles)
141 particle_set => subsys%particles%els
142 atomic_kind_set => subsys%atomic_kinds%els
143 molecule_set => subsys%molecules%els
144 molecule_kind_set => subsys%molecule_kinds%els
145
146 ! Create the mixed_energy_type
147 CALL allocate_mixed_energy(mixed_energy)
148
149 ! Print the molecule kind set
150 CALL write_molecule_kind_set(molecule_kind_set, subsys_section)
151
152 ! Distribute molecules and atoms using the new data structures ***
153 CALL distribute_molecules_1d(atomic_kind_set=atomic_kind_set, &
154 particle_set=particle_set, &
155 local_particles=local_particles, &
156 molecule_kind_set=molecule_kind_set, &
157 molecule_set=molecule_set, &
158 local_molecules=local_molecules, &
159 force_env_section=force_env_section)
160
161 CALL cp_subsys_set(subsys, cell=cell)
162
163 ! set the mixed_env
164 CALL set_mixed_env(mixed_env=mixed_env, subsys=subsys)
165 CALL set_mixed_env(mixed_env=mixed_env, &
166 cell_ref=cell_ref, &
167 local_molecules=local_molecules, &
168 local_particles=local_particles, &
169 mixed_energy=mixed_energy)
170
171 CALL distribution_1d_release(local_particles)
172 CALL distribution_1d_release(local_molecules)
173
174 CALL timestop(handle)
175
176 END SUBROUTINE mixed_init_subsys
177
178END MODULE mixed_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
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
Interface to the message passing library MPI.
subroutine, public allocate_mixed_energy(mixed_energy)
Allocate and/or initialise a mixed energy data structure.
subroutine, public set_mixed_env(mixed_env, atomic_kind_set, particle_set, local_particles, local_molecules, molecule_kind_set, molecule_set, cell_ref, mixed_energy, subsys, input, sub_para_env, cdft_control)
Set the MIXED environment.
initialize mixed environment
subroutine, public mixed_init(mixed_env, root_section, para_env, force_env_section, use_motion_section)
reads the input and database file for mixed
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.
stores all the informations relevant to an mpi environment