(git:34ef472)
ipi_driver.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 Driver mode - To communicate with i-PI Python wrapper
10 !> \par History
11 !> none
12 !> \author Michele Ceriotti 03.2012
13 ! **************************************************************************************************
14 MODULE ipi_driver
15  USE iso_c_binding, ONLY: c_char, &
16  c_double, &
17  c_int, &
18  c_loc, &
19  c_null_char, &
20  c_ptr
21  USE bibliography, ONLY: ceriotti2014, &
22  kapil2016, &
23  cite_reference
24  USE cell_methods, ONLY: cell_create, &
25  init_cell
26  USE cell_types, ONLY: cell_release, &
27  cell_type
30  USE cp_subsys_types, ONLY: cp_subsys_get, &
31  cp_subsys_set, &
32  cp_subsys_type
34  USE force_env_types, ONLY: force_env_get, &
35  force_env_type
36  USE global_types, ONLY: global_environment_type
38  section_vals_type, &
40  USE kinds, ONLY: default_path_length, &
42  dp, &
43  int_4
44  USE message_passing, ONLY: mp_para_env_type, &
45  mp_request_type, &
46  mp_testany
47 #ifndef __NO_SOCKETS
48  USE sockets_interface, ONLY: writebuffer, &
49  readbuffer, &
51  uwait
52 #endif
53  USE virial_types, ONLY: virial_type
54 #include "./base/base_uses.f90"
55 
56  IMPLICIT NONE
57 
58  PRIVATE
59 
60  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'ipi_driver'
61 
62  PUBLIC :: run_driver
63 
64 CONTAINS
65 
66 ! **************************************************************************************************
67 !> \brief ...
68 !> \param force_env ...
69 !> \param globenv ...
70 !> \par History
71 !> 12.2013 included in repository
72 !> \author Ceriotti
73 ! **************************************************************************************************
74 
75  SUBROUTINE run_driver(force_env, globenv)
76  TYPE(force_env_type), POINTER :: force_env
77  TYPE(global_environment_type), POINTER :: globenv
78 
79  CHARACTER(len=*), PARAMETER :: routinen = 'run_driver'
80 
81 #ifdef __NO_SOCKETS
82  INTEGER :: handle
83  CALL timeset(routinen, handle)
84  cpabort("CP2K was compiled with the __NO_SOCKETS option!")
85  mark_used(globenv)
86  mark_used(force_env)
87 #else
88  INTEGER, PARAMETER :: msglen = 12
89 
90  CHARACTER(len=default_path_length) :: c_hostname, drv_hostname
91  CHARACTER(LEN=default_string_length) :: header
92  INTEGER :: drv_port, handle, i_drv_unix, &
93  idir, ii, inet, ip, iwait, &
94  nat, output_unit, socket
95  TYPE(mp_request_type), DIMENSION(2) :: wait_req
96  INTEGER(KIND=int_4), POINTER :: wait_msg(:)
97  LOGICAL :: drv_unix, fwait, hasdata, &
98  ionode, should_stop
99  REAL(kind=dp) :: cellh(3, 3), cellih(3, 3), &
100  mxmat(9), pot, vir(3, 3)
101  REAL(kind=dp), ALLOCATABLE :: combuf(:)
102  TYPE(cell_type), POINTER :: cpcell
103  TYPE(mp_para_env_type), POINTER :: para_env
104  TYPE(cp_subsys_type), POINTER :: subsys
105  TYPE(section_vals_type), POINTER :: drv_section, motion_section
106  TYPE(virial_type), POINTER :: virial
107  REAL(kind=dp) :: sleeptime
108 
109  CALL timeset(routinen, handle)
110 
111  CALL cite_reference(ceriotti2014)
112  CALL cite_reference(kapil2016)
113 
114 ! server address parsing
115 ! buffers and temporaries for communication
116 ! access cp2k structures
117 
118  cpassert(ASSOCIATED(force_env))
119  CALL force_env_get(force_env, para_env=para_env)
120 
121  hasdata = .false.
122  ionode = para_env%is_source()
123 
124  output_unit = cp_logger_get_default_io_unit()
125 
126  ! reads driver parameters from input
127  motion_section => section_vals_get_subs_vals(force_env%root_section, "MOTION")
128  drv_section => section_vals_get_subs_vals(motion_section, "DRIVER")
129 
130  CALL section_vals_val_get(drv_section, "HOST", c_val=drv_hostname)
131  CALL section_vals_val_get(drv_section, "PORT", i_val=drv_port)
132  CALL section_vals_val_get(drv_section, "UNIX", l_val=drv_unix)
133  CALL section_vals_val_get(drv_section, "SLEEP_TIME", r_val=sleeptime)
134  cpassert(sleeptime >= 0)
135 
136  ! opens the socket
137  socket = 0
138  inet = 1
139  i_drv_unix = 1 ! a bit convoluted. socket.c uses a different convention...
140  IF (drv_unix) i_drv_unix = 0
141  IF (output_unit > 0) THEN
142  WRITE (output_unit, *) "@ i-PI DRIVER BEING LOADED"
143  WRITE (output_unit, *) "@ INPUT DATA: ", trim(drv_hostname), drv_port, drv_unix
144  END IF
145 
146  c_hostname = trim(drv_hostname)//c_null_char
147  IF (ionode) CALL open_connect_socket(socket, i_drv_unix, drv_port, c_hostname)
148 
149  NULLIFY (wait_msg)
150  ALLOCATE (wait_msg(1))
151  !now we have a socket, so we can initialize the CP2K environments.
152  NULLIFY (cpcell)
153  CALL cell_create(cpcell)
154  driver_loop: DO
155  ! do communication on master node only...
156  header = ""
157 
158  CALL para_env%sync()
159 
160  ! non-blocking sync to avoid useless CPU consumption
161  IF (ionode) THEN
162  CALL readbuffer(socket, header, msglen)
163  wait_msg = 0
164  DO iwait = 0, para_env%num_pe - 1
165  IF (iwait /= para_env%source) THEN
166  CALL para_env%send(msg=wait_msg, dest=iwait, tag=666)
167  END IF
168  END DO
169  ELSE
170  CALL para_env%irecv(msgout=wait_msg, source=para_env%source, &
171  tag=666, request=wait_req(2))
172  CALL mp_testany(wait_req(2:), flag=fwait)
173  DO WHILE (.NOT. fwait)
174  CALL mp_testany(wait_req(2:), flag=fwait)
175  CALL uwait(sleeptime)
176  END DO
177  END IF
178 
179  CALL para_env%sync()
180 
181  CALL para_env%bcast(header)
182 
183  IF (output_unit > 0) WRITE (output_unit, *) " @ DRIVER MODE: Message from server: ", trim(header)
184  IF (trim(header) == "STATUS") THEN
185 
186  CALL para_env%sync()
187  IF (ionode) THEN ! does not need init (well, maybe it should, just to check atom numbers and the like... )
188  IF (hasdata) THEN
189  CALL writebuffer(socket, "HAVEDATA ", msglen)
190  ELSE
191  CALL writebuffer(socket, "READY ", msglen)
192  END IF
193  END IF
194  CALL para_env%sync()
195  ELSE IF (trim(header) == "POSDATA") THEN
196  IF (ionode) THEN
197  CALL readbuffer(socket, mxmat, 9)
198  cellh = reshape(mxmat, (/3, 3/))
199  CALL readbuffer(socket, mxmat, 9)
200  cellih = reshape(mxmat, (/3, 3/))
201  CALL readbuffer(socket, nat)
202  cellh = transpose(cellh)
203  cellih = transpose(cellih)
204  END IF
205  CALL para_env%bcast(cellh)
206  CALL para_env%bcast(cellih)
207  CALL para_env%bcast(nat)
208  IF (.NOT. ALLOCATED(combuf)) ALLOCATE (combuf(3*nat))
209  IF (ionode) CALL readbuffer(socket, combuf, nat*3)
210  CALL para_env%bcast(combuf)
211 
212  CALL force_env_get(force_env, subsys=subsys)
213  IF (nat /= subsys%particles%n_els) &
214  cpabort("@DRIVER MODE: Uh-oh! Particle number mismatch between i-PI and cp2k input!")
215  ii = 0
216  DO ip = 1, subsys%particles%n_els
217  DO idir = 1, 3
218  ii = ii + 1
219  subsys%particles%els(ip)%r(idir) = combuf(ii)
220  END DO
221  END DO
222  CALL init_cell(cpcell, hmat=cellh)
223  CALL cp_subsys_set(subsys, cell=cpcell)
224 
225  CALL force_env_calc_energy_force(force_env, calc_force=.true.)
226 
227  IF (output_unit > 0) WRITE (output_unit, *) " @ DRIVER MODE: Received positions "
228 
229  combuf = 0
230  ii = 0
231  DO ip = 1, subsys%particles%n_els
232  DO idir = 1, 3
233  ii = ii + 1
234  combuf(ii) = subsys%particles%els(ip)%f(idir)
235  END DO
236  END DO
237  CALL force_env_get(force_env, potential_energy=pot)
238  CALL force_env_get(force_env, cell=cpcell)
239  CALL cp_subsys_get(subsys, virial=virial)
240  vir = transpose(virial%pv_virial)
241 
242  CALL external_control(should_stop, "IPI", globenv=globenv)
243  IF (should_stop) EXIT
244 
245  hasdata = .true.
246  ELSE IF (trim(header) == "GETFORCE") THEN
247  IF (output_unit > 0) WRITE (output_unit, *) " @ DRIVER MODE: Returning v,forces,stress "
248  IF (ionode) THEN
249  CALL writebuffer(socket, "FORCEREADY ", msglen)
250  CALL writebuffer(socket, pot)
251  CALL writebuffer(socket, nat)
252  CALL writebuffer(socket, combuf, 3*nat)
253  CALL writebuffer(socket, reshape(vir, (/9/)), 9)
254 
255  ! i-pi can also receive an arbitrary string, that will be printed out to the "extra"
256  ! trajectory file. this is useful if you want to return additional information, e.g.
257  ! atomic charges, wannier centres, etc. one must return the number of characters, then
258  ! the string. here we just send back zero characters.
259  nat = 0
260  CALL writebuffer(socket, nat) ! writes out zero for the length of the "extra" field (not implemented yet!)
261  END IF
262  hasdata = .false.
263  ELSE
264  IF (output_unit > 0) WRITE (output_unit, *) " @DRIVER MODE: Socket disconnected, time to exit. "
265  EXIT
266  END IF
267  END DO driver_loop
268 
269  ! clean up
270  CALL cell_release(cpcell)
271  DEALLOCATE (wait_msg)
272 #endif
273 
274  CALL timestop(handle)
275 
276  END SUBROUTINE run_driver
277 END MODULE ipi_driver
collects all references to literature in CP2K as new algorithms / method are included from literature...
Definition: bibliography.F:28
integer, save, public kapil2016
Definition: bibliography.F:43
integer, save, public ceriotti2014
Definition: bibliography.F:43
Handles all functions related to the CELL.
Definition: cell_methods.F:15
subroutine, public init_cell(cell, hmat, periodic)
Initialise/readjust a simulation cell after hmat has been changed.
Definition: cell_methods.F:117
subroutine, public cell_create(cell, hmat, periodic, tag)
allocates and initializes a cell
Definition: cell_methods.F:85
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
Routines to handle the external control of CP2K.
subroutine, public external_control(should_stop, flag, globenv, target_time, start_time, force_check)
External manipulations during a run : when the <PROJECT_NAME>.EXIT_$runtype command is sent the progr...
various routines to log and control the output. The idea is that decisions about where to log should ...
integer function, public cp_logger_get_default_io_unit(logger)
returns the unit nr for the ionode (-1 on all other processors) skips as well checks if the procs cal...
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
subroutine, public cp_subsys_get(subsys, ref_count, atomic_kinds, atomic_kind_set, particles, particle_set, local_particles, molecules, molecule_set, molecule_kinds, molecule_kind_set, local_molecules, para_env, colvar_p, shell_particles, core_particles, gci, multipoles, natom, nparticle, ncore, nshell, nkind, atprop, virial, results, cell)
returns information about various attributes of the given subsys
Interface for the force calculations.
recursive subroutine, public force_env_calc_energy_force(force_env, calc_force, consistent_energies, skip_external_control, eval_energy_forces, require_consistent_energy_force, linres, calc_stress_tensor)
Interface routine for force and energy calculations.
Interface for the force calculations.
recursive subroutine, public force_env_get(force_env, in_use, fist_env, qs_env, meta_env, fp_env, subsys, para_env, potential_energy, additional_potential, kinetic_energy, harmonic_shell, kinetic_shell, cell, sub_force_env, qmmm_env, qmmmx_env, eip_env, pwdft_env, globenv, input, force_env_section, method_name_id, root_section, mixed_env, nnp_env, embed_env)
returns various attributes about the force environment
Define type storing the global information of a run. Keep the amount of stored data small....
Definition: global_types.F:21
Definition: header.F:13
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
subroutine, public section_vals_val_get(section_vals, keyword_name, i_rep_section, i_rep_val, n_rep_val, val, l_val, i_val, r_val, c_val, l_vals, i_vals, r_vals, c_vals, explicit)
returns the requested value
Driver mode - To communicate with i-PI Python wrapper.
Definition: ipi_driver.F:14
subroutine, public run_driver(force_env, globenv)
...
Definition: ipi_driver.F:76
Defines the basic variable types.
Definition: kinds.F:23
integer, parameter, public dp
Definition: kinds.F:34
integer, parameter, public default_string_length
Definition: kinds.F:57
integer, parameter, public default_path_length
Definition: kinds.F:58
integer, parameter, public int_4
Definition: kinds.F:51
Interface to the message passing library MPI.
Implements UNIX and INET sockets.
void writebuffer(int *psockfd, char *data, int *plen)
Writes to a socket.
Definition: sockets.c:201
void uwait(double *dsec)
Mini-wrapper to nanosleep.
Definition: sockets.c:279
void readbuffer(int *psockfd, char *data, int *plen)
Reads from a socket.
Definition: sockets.c:219