(git:7f1b8e3)
Loading...
Searching...
No Matches
mimic_communicator.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 Module containing a MiMiC communicator class
10!> \par History
11!> 05.2025 Created [AA]
12!> \author Andrej Antalik
13! **************************************************************************************************
14
16
27 USE kinds, ONLY: default_string_length,&
28 dp
29 USE mcl_api, ONLY: mcl_finalize,&
34 USE mcl_requests, ONLY: mcl_data,&
40 USE pw_env_types, ONLY: pw_env_get,&
43 USE pw_types, ONLY: pw_r3d_rs_type
48 USE qs_kind_types, ONLY: get_qs_kind,&
50 USE qs_ks_types, ONLY: qs_ks_env_type,&
52 USE qs_rho_types, ONLY: qs_rho_get,&
54#include "../base/base_uses.f90"
55
56 IMPLICIT NONE
57
58 PRIVATE
59
60 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'mimic_communicator'
61
62! **************************************************************************************************
63!> \brief MiMiC communicator class that facilitates MiMiC client-server data exchange
64!> \par History
65!> 05.2025 Created [AA]
66! **************************************************************************************************
68 PRIVATE
69 !> communication
70 TYPE(mp_para_env_type), POINTER :: para_env => null()
71 LOGICAL :: is_ionode = .false.
72 INTEGER :: mcl_server = 0, &
73 client_id = -1
74 !> CP2K data
75 TYPE(force_env_type), POINTER :: force_env => null()
76 TYPE(pw_pool_type), POINTER :: pw_info => null()
77 TYPE(particle_list_type), POINTER :: atoms => null()
78 TYPE(atomic_kind_list_type), POINTER :: kinds => null()
79 TYPE(qs_energy_type), POINTER :: energy => null()
80 TYPE(pw_r3d_rs_type), POINTER :: potential => null()
81 TYPE(qs_rho_type), POINTER :: density => null()
82 INTEGER :: n_atoms = -1, &
83 n_kinds = -1, &
84 n_spins = -1
85 INTEGER, DIMENSION(:, :), ALLOCATABLE :: npts_pproc
86 !> beginning index of the local buffer in the global buffer diminished by 1
87 INTEGER, DIMENSION(:), ALLOCATABLE :: lb_pproc
88
89 CONTAINS
90
91 PROCEDURE :: initialize
92 PROCEDURE :: finalize
93 PROCEDURE :: receive_request
94 PROCEDURE :: send_value
95 PROCEDURE :: send_client_info
96 PROCEDURE :: send_atom_info
97 PROCEDURE :: send_kind_info
98 PROCEDURE :: send_box_info
99 PROCEDURE :: send_result
100 PROCEDURE :: send_grid_coordinates
101 PROCEDURE :: send_density
102 PROCEDURE :: send_forces
103 PROCEDURE :: send_positions
104 PROCEDURE :: receive_positions
105 PROCEDURE :: receive_potential
106
108
109CONTAINS
110
111! **************************************************************************************************
112!> \brief Initialize the communicator by loading data and saving pointers to relevant data
113!> \param this ...
114!> \param force_env ...
115!> \par History
116!> 05.2025 Created [AA]
117! **************************************************************************************************
118 SUBROUTINE initialize(this, force_env)
119 CLASS(mimic_communicator_type), INTENT(INOUT) :: this
120 TYPE(force_env_type), TARGET :: force_env
121
122 CHARACTER(LEN=*), PARAMETER :: routineN = modulen//':initialize'
123
124 TYPE(cp_subsys_type), POINTER :: subsys
125 TYPE(dft_control_type), POINTER :: dft_control
126 TYPE(pw_env_type), POINTER :: pw_env
127 TYPE(qs_environment_type), POINTER :: qs_env
128 TYPE(qs_ks_env_type), POINTER :: ks_env
129 INTEGER :: handle
130
131 CALL timeset(routinen, handle)
132
133 CALL mcl_get_program_id(this%client_id)
134
135 NULLIFY (subsys, qs_env, ks_env, pw_env)
136 this%force_env => force_env
137 CALL force_env_get(this%force_env, subsys=subsys, para_env=this%para_env, qs_env=qs_env)
138 CALL cp_subsys_get(subsys, natom=this%n_atoms, particles=this%atoms, &
139 nkind=this%n_kinds, atomic_kinds=this%kinds)
140 CALL get_qs_env(qs_env, energy=this%energy, vee=this%potential, rho=this%density, &
141 dft_control=dft_control, ks_env=ks_env, pw_env=pw_env)
142 CALL pw_env_get(pw_env, auxbas_pw_pool=this%pw_info)
143
144 this%is_ionode = this%para_env%is_source()
145
146 ALLOCATE (this%npts_pproc(3, 0:this%para_env%num_pe - 1), source=0)
147 this%npts_pproc(:, this%para_env%mepos) = this%pw_info%pw_grid%npts_local
148 CALL this%para_env%sum(this%npts_pproc)
149
150 ALLOCATE (this%lb_pproc(0:this%para_env%num_pe - 1), source=0)
151 this%lb_pproc(this%para_env%mepos) = this%pw_info%pw_grid%bounds_local(1, 1) &
152 - this%pw_info%pw_grid%bounds(1, 1)
153 CALL this%para_env%sum(this%lb_pproc)
154
155 this%n_spins = dft_control%nspins
156
157 CALL set_qs_env(qs_env, mimic=.true.)
158 dft_control%apply_external_potential = .true.
159 dft_control%eval_external_potential = .false.
160
161 ! allocate external electrostatic potential
162 IF (ASSOCIATED(this%potential)) THEN
163 CALL this%potential%release()
164 DEALLOCATE (this%potential)
165 END IF
166 ALLOCATE (this%potential)
167 CALL this%pw_info%create_pw(this%potential)
168 CALL set_ks_env(ks_env, vee=this%potential)
169
170 CALL timestop(handle)
171
172 END SUBROUTINE initialize
173
174! **************************************************************************************************
175!> \brief Finalize the simulation by deallocating memory
176!> \param this ...
177! **************************************************************************************************
178 SUBROUTINE finalize(this)
179 CLASS(mimic_communicator_type), INTENT(INOUT) :: this
180
181 CHARACTER(LEN=*), PARAMETER :: routineN = modulen//':finalize'
182
183 INTEGER :: handle
184
185 CALL timeset(routinen, handle)
186
187 CALL this%para_env%sync()
188
189 CALL mcl_finalize()
190
191 CALL timestop(handle)
192
193 END SUBROUTINE finalize
194
195! **************************************************************************************************
196!> \brief Receive a request from the server
197!> \param this ...
198!> \return ...
199! **************************************************************************************************
200 FUNCTION receive_request(this) RESULT(request)
201 CLASS(mimic_communicator_type), INTENT(INOUT) :: this
202 INTEGER :: request
203
204 CHARACTER(LEN=*), PARAMETER :: routineN = modulen//':receive_request'
205
206 INTEGER :: handle
207
208 CALL timeset(routinen, handle)
209
210 request = -1
211 CALL mcl_receive(request, 1, mcl_request, this%mcl_server)
212 CALL this%para_env%bcast(request)
213
214 CALL timestop(handle)
215
216 END FUNCTION receive_request
217
218! **************************************************************************************************
219!> \brief Send the specified single value data to the server
220!> \param this ...
221!> \param option word corresponding to available options
222!> \note Several values hardcoded for now
223! **************************************************************************************************
224 SUBROUTINE send_value(this, option)
225 CLASS(mimic_communicator_type), INTENT(INOUT) :: this
226 CHARACTER(LEN=*) :: option
227
228 CHARACTER(LEN=*), PARAMETER :: routineN = modulen//':send_value'
229
230 REAL(dp) :: energy
231 INTEGER :: handle
232
233 CALL timeset(routinen, handle)
234
235 SELECT CASE (option)
236 CASE ("num_atoms", "num_atoms_in_fragments")
237 CALL mcl_send(this%n_atoms, 1, mcl_data, this%mcl_server)
238 CASE ("num_kinds")
239 CALL mcl_send(this%n_kinds, 1, mcl_data, this%mcl_server)
240 CASE ("num_fragments")
241 CALL mcl_send(1, 1, mcl_data, this%mcl_server)
242 CASE ("num_bonds") ! later use to communicate constraints
243 CALL mcl_send(0, 1, mcl_data, this%mcl_server)
244 CASE ("num_angles") ! later use to communicate constraints
245 CALL mcl_send(0, 1, mcl_data, this%mcl_server)
246 CASE ("energy")
247 energy = this%energy%total - this%energy%ee
248 CALL mcl_send(energy, 1, mcl_data, this%mcl_server)
249 CASE DEFAULT
250 cpabort("The value chosen in "//routinen//" is not implemented.")
251 END SELECT
252
253 CALL timestop(handle)
254
255 END SUBROUTINE send_value
256
257! **************************************************************************************************
258!> \brief Send the specified information about the client to the server
259!> \param this ...
260!> \param option word corresponding to available options
261! **************************************************************************************************
262 SUBROUTINE send_client_info(this, option)
263 CLASS(mimic_communicator_type), INTENT(INOUT) :: this
264 CHARACTER(LEN=*) :: option
265
266 CHARACTER(LEN=*), PARAMETER :: routineN = modulen//':send_client_info'
267
268 CHARACTER(LEN=*), PARAMETER :: client_name = "CP2K"
269 INTEGER, DIMENSION(3) :: api_version
270 INTEGER :: handle, length
271
272 CALL timeset(routinen, handle)
273
274 SELECT CASE (option)
275 CASE ("id")
276 CALL mcl_send(this%client_id, 1, mcl_data, this%mcl_server)
277 CASE ("name")
278 length = len(client_name)
279 CALL mcl_send(length, 1, mcl_length, this%mcl_server)
280 CALL mcl_send(client_name, length, mcl_data, this%mcl_server)
281 CASE ("run_type")
282 CALL mcl_send(mcl_runtype_qm_rs_grid, 1, mcl_data, this%mcl_server)
283 CASE ("api_version")
284 CALL mcl_get_api_version(api_version)
285 CALL mcl_send(api_version, 3, mcl_data, this%mcl_server)
286 CASE DEFAULT
287 cpabort("The value chosen in "//routinen//" is not implemented.")
288 END SELECT
289
290 CALL timestop(handle)
291
292 END SUBROUTINE send_client_info
293
294! **************************************************************************************************
295!> \brief Send the specified data for each atom to the server
296!> \param this ...
297!> \param option word corresponding to available options
298! **************************************************************************************************
299 SUBROUTINE send_atom_info(this, option)
300 CLASS(mimic_communicator_type), INTENT(INOUT) :: this
301 CHARACTER(LEN=*) :: option
302
303 CHARACTER(LEN=*), PARAMETER :: routineN = modulen//':send_atom_info'
304
305 INTEGER, DIMENSION(:), ALLOCATABLE :: buffer
306 INTEGER :: handle, i
307
308 CALL timeset(routinen, handle)
309
310 ALLOCATE (buffer(this%n_atoms))
311 SELECT CASE (option)
312 CASE ("kinds")
313 DO i = 1, this%n_atoms
314 buffer(i) = this%atoms%els(i)%atomic_kind%kind_number
315 END DO
316 CASE ("ids")
317 DO i = 1, this%n_atoms
318 buffer(i) = this%atoms%els(i)%atom_index
319 END DO
320 CASE DEFAULT
321 cpabort("The value chosen in "//routinen//" is not implemented.")
322 END SELECT
323 CALL mcl_send(buffer, SIZE(buffer), mcl_data, this%mcl_server)
324
325 CALL timestop(handle)
326
327 END SUBROUTINE send_atom_info
328
329! **************************************************************************************************
330!> \brief Send the specified data for each kind to the server
331!> \param this ...
332!> \param option word corresponding to available options
333! **************************************************************************************************
334 SUBROUTINE send_kind_info(this, option)
335 CLASS(mimic_communicator_type), INTENT(INOUT) :: this
336 CHARACTER(LEN=*) :: option
337
338 CHARACTER(LEN=*), PARAMETER :: routineN = modulen//':send_kind_info'
339
340 TYPE(qs_environment_type), POINTER :: qs_env
341 TYPE(qs_kind_type), DIMENSION(:), POINTER :: qs_kinds
342 REAL(dp), DIMENSION(:), ALLOCATABLE :: buffer_dp
343 INTEGER, DIMENSION(:), ALLOCATABLE :: buffer_i
344 CHARACTER(LEN=:), ALLOCATABLE :: labels
345 CHARACTER(LEN=default_string_length) :: label
346 INTEGER :: handle, length, i
347
348 CALL timeset(routinen, handle)
349
350 SELECT CASE (option)
351 CASE ("labels")
352 ALLOCATE (CHARACTER(30*this%n_kinds) :: labels)
353 labels = ""
354 DO i = 1, this%n_kinds
355 CALL get_atomic_kind(this%kinds%els(i), name=label)
356 labels = trim(labels)//trim(label)//","
357 END DO
358 length = len(trim(labels)) - 1
359 CALL mcl_send(length, 1, mcl_length, this%mcl_server)
360 CALL mcl_send(labels, length, mcl_data, this%mcl_server)
361 CASE ("elements")
362 ALLOCATE (buffer_i(this%n_kinds))
363 DO i = 1, this%n_kinds
364 CALL get_atomic_kind(this%kinds%els(i), z=buffer_i(i))
365 END DO
366 CALL mcl_send(buffer_i, SIZE(buffer_i), mcl_data, this%mcl_server)
367 CASE ("masses")
368 ALLOCATE (buffer_dp(this%n_kinds))
369 DO i = 1, this%n_kinds
370 buffer_dp(i) = cp_unit_from_cp2k(this%kinds%els(i)%mass, "AMU")
371 END DO
372 CALL mcl_send(buffer_dp, SIZE(buffer_dp), mcl_data, this%mcl_server)
373 CASE ("nuclear_charges")
374 NULLIFY (qs_env, qs_kinds)
375 CALL force_env_get(this%force_env, qs_env=qs_env)
376 CALL get_qs_env(qs_env, qs_kind_set=qs_kinds)
377 ALLOCATE (buffer_dp(this%n_kinds))
378 DO i = 1, this%n_kinds
379 CALL get_qs_kind(qs_kinds(i), zeff=buffer_dp(i))
380 END DO
381 CALL mcl_send(buffer_dp, SIZE(buffer_dp), mcl_data, this%mcl_server)
382 CASE DEFAULT
383 cpabort("The value chosen in "//routinen//" is not implemented.")
384 END SELECT
385
386 CALL timestop(handle)
387
388 END SUBROUTINE send_kind_info
389
390! **************************************************************************************************
391!> \brief Send the specified box information to the server
392!> \param this ...
393!> \param option word corresponding to available options
394! **************************************************************************************************
395 SUBROUTINE send_box_info(this, option)
396 CLASS(mimic_communicator_type), INTENT(INOUT) :: this
397 CHARACTER(LEN=*) :: option
398
399 CHARACTER(LEN=*), PARAMETER :: routineN = modulen//':send_box_info'
400
401 INTEGER, DIMENSION(3) :: npts_glob
402 REAL(dp), DIMENSION(3) :: origin
403 REAL(dp), DIMENSION(9) :: box_vectors
404 INTEGER :: handle, i
405
406 CALL timeset(routinen, handle)
407
408 npts_glob = this%pw_info%pw_grid%npts
409
410 SELECT CASE (option)
411 CASE ("num_gridpoints")
412 CALL mcl_send(npts_glob, 3, mcl_data, this%mcl_server)
413 CASE ("origin")
414 origin = 0.0_dp
415 CALL mcl_send(origin, 3, mcl_data, this%mcl_server)
416 CASE ("box_vectors")
417 box_vectors = [(this%pw_info%pw_grid%dh(:, i)*real(npts_glob(i), dp), i=1, 3)]
418 CALL mcl_send(box_vectors, 9, mcl_data, this%mcl_server)
419 CASE DEFAULT
420 cpabort("The value chosen in "//routinen//" is not implemented.")
421 END SELECT
422
423 CALL timestop(handle)
424
425 END SUBROUTINE send_box_info
426
427! **************************************************************************************************
428!> \brief Send the specified result to the server
429!> \param this ...
430!> \param option word corresponding to available options
431! **************************************************************************************************
432 SUBROUTINE send_result(this, option)
433 CLASS(mimic_communicator_type), INTENT(INOUT) :: this
434 CHARACTER(LEN=*) :: option
435
436 CHARACTER(LEN=*), PARAMETER :: routineN = modulen//':send_result'
437
438 TYPE(qs_environment_type), POINTER :: qs_env
439 TYPE(cp_result_type), POINTER :: results
440 CHARACTER(LEN=default_string_length) :: description
441 REAL(KIND=dp), DIMENSION(:), ALLOCATABLE :: buffer
442 INTEGER :: handle
443
444 CALL timeset(routinen, handle)
445
446 NULLIFY (qs_env, results)
447 CALL force_env_get(this%force_env, qs_env=qs_env)
448 CALL get_qs_env(qs_env, results=results)
449
450 SELECT CASE (option)
451 CASE ("hirshfeld_charges")
452 description = "[HIRSHFELD-CHARGES]"
453 ALLOCATE (buffer(this%n_atoms), source=0.0_dp)
454 CALL get_results(results, description, buffer)
455 CALL mcl_send(buffer, SIZE(buffer), mcl_data, this%mcl_server)
456 CASE DEFAULT
457 cpabort("The value chosen in "//routinen//" is not implemented.")
458 END SELECT
459
460 CALL timestop(handle)
461
462 END SUBROUTINE send_result
463
464! **************************************************************************************************
465!> \brief Send grid point coordinates to the server
466!> \param this ...
467! **************************************************************************************************
468 SUBROUTINE send_grid_coordinates(this)
469 CLASS(mimic_communicator_type), INTENT(INOUT) :: this
470
471 CHARACTER(LEN=*), PARAMETER :: routineN = modulen//':send_grid_coordinates'
472
473 INTEGER, DIMENSION(3) :: npts_glob, npts, lb_glob, lb, ub
474 REAL(dp), DIMENSION(3) :: origin
475 REAL(dp), DIMENSION(3, 3) :: box_vectors
476 REAL(dp), DIMENSION(:, :), ALLOCATABLE :: coords
477 INTEGER :: handle, i, j, k, offset
478
479 CALL timeset(routinen, handle)
480
481 origin = 0.0_dp
482 box_vectors = this%pw_info%pw_grid%dh
483 ! number of grid points
484 npts_glob = this%pw_info%pw_grid%npts
485 npts = this%pw_info%pw_grid%npts_local
486 ! bounds
487 lb_glob = this%pw_info%pw_grid%bounds(1, :)
488 lb = this%pw_info%pw_grid%bounds_local(1, :)
489 ub = this%pw_info%pw_grid%bounds_local(2, :)
490
491 ALLOCATE (coords(3, product(npts_glob)), source=0.0_dp)
492 offset = (lb(1) - lb_glob(1))*product(npts(2:))
493 DO k = lb(3), ub(3)
494 DO j = lb(2), ub(2)
495 DO i = lb(1), ub(1)
496 offset = offset + 1
497 coords(:, offset) = origin + box_vectors(:, 1)*real(i - lb_glob(1), dp) &
498 + box_vectors(:, 2)*real(j - lb_glob(2), dp) &
499 + box_vectors(:, 3)*real(k - lb_glob(3), dp)
500 END DO
501 END DO
502 END DO
503 CALL this%para_env%sum(coords)
504
505 CALL mcl_send(coords, SIZE(coords), mcl_data, this%mcl_server)
506
507 CALL timestop(handle)
508
509 END SUBROUTINE send_grid_coordinates
510
511! **************************************************************************************************
512!> \brief Receive external potential from the server
513!> \param this ...
514! **************************************************************************************************
515 SUBROUTINE receive_potential(this)
516 CLASS(mimic_communicator_type), INTENT(INOUT) :: this
517
518 CHARACTER(LEN=*), PARAMETER :: routineN = modulen//':receive_potential'
519
520 INTEGER, DIMENSION(3) :: npts, lb, ub
521 REAL(dp), DIMENSION(:), ALLOCATABLE, TARGET :: buffer
522 REAL(dp), DIMENSION(:), ALLOCATABLE :: buffer_loc
523 REAL(dp), DIMENSION(:), POINTER :: buffer_p
524 INTEGER :: i, j, k, i_proc, offset
525 INTEGER :: handle, length, tag
526
527 CALL timeset(routinen, handle)
528
529 NULLIFY (buffer_p)
530 npts = this%pw_info%pw_grid%npts_local
531 lb = this%pw_info%pw_grid%bounds_local(1, :)
532 ub = this%pw_info%pw_grid%bounds_local(2, :)
533 ALLOCATE (buffer_loc(product(npts)))
534
535 tag = 1
536
537 IF (this%is_ionode) THEN
538 ALLOCATE (buffer(product(this%pw_info%pw_grid%npts)))
539 ! receive potential at the IO process
540 CALL mcl_receive(buffer, SIZE(buffer), mcl_data, this%mcl_server)
541 ! distribute across processes
542 DO i_proc = 0, this%para_env%num_pe - 1
543 length = product(this%npts_pproc(:, i_proc))
544 offset = this%lb_pproc(i_proc)*product(npts(2:)) + 1
545 buffer_p => buffer(offset:offset + length - 1)
546 IF (i_proc /= this%para_env%source) THEN
547 i = i_proc
548 CALL this%para_env%send(buffer_p, i, tag)
549 ELSE
550 buffer_loc(:) = buffer_p
551 END IF
552 END DO
553 ELSE
554 CALL this%para_env%recv(buffer_loc, this%para_env%source, tag)
555 END IF
556
557 ! set the potential
558 offset = 0
559 DO k = lb(3), ub(3)
560 DO j = lb(2), ub(2)
561 DO i = lb(1), ub(1)
562 offset = offset + 1
563 this%potential%array(i, j, k) = -buffer_loc(offset)
564 END DO
565 END DO
566 END DO
567
568 CALL timestop(handle)
569
570 END SUBROUTINE receive_potential
571
572! **************************************************************************************************
573!> \brief Send electron density to the server
574!> \param this ...
575! **************************************************************************************************
576 SUBROUTINE send_density(this)
577 CLASS(mimic_communicator_type), INTENT(INOUT) :: this
578
579 CHARACTER(LEN=*), PARAMETER :: routineN = modulen//':send_density'
580
581 INTEGER, DIMENSION(3) :: npts, lb, ub
582 TYPE(pw_r3d_rs_type), DIMENSION(:), POINTER :: rho
583 REAL(dp), DIMENSION(:), ALLOCATABLE, TARGET :: buffer
584 REAL(dp), DIMENSION(:), ALLOCATABLE :: buffer_loc
585 REAL(dp), DIMENSION(:), POINTER :: buffer_p
586 INTEGER :: i_spin, i_proc, i, j, k, offset
587 INTEGER :: handle, length, tag
588
589 CALL timeset(routinen, handle)
590
591 NULLIFY (rho, buffer_p)
592 CALL qs_rho_get(this%density, rho_r=rho)
593 npts = this%pw_info%pw_grid%npts_local
594 lb = this%pw_info%pw_grid%bounds_local(1, :)
595 ub = this%pw_info%pw_grid%bounds_local(2, :)
596 ALLOCATE (buffer_loc(product(npts)))
597
598 ! gather density values
599 buffer_loc = 0.0_dp
600 DO i_spin = 1, this%n_spins
601 offset = 0
602 DO k = lb(3), ub(3)
603 DO j = lb(2), ub(2)
604 DO i = lb(1), ub(1)
605 offset = offset + 1
606 buffer_loc(offset) = buffer_loc(offset) + rho(i_spin)%array(i, j, k)
607 END DO
608 END DO
609 END DO
610 END DO
611
612 tag = 1
613
614 IF (.NOT. this%is_ionode) THEN
615 CALL this%para_env%send(buffer_loc, this%para_env%source, tag)
616 ELSE
617 ALLOCATE (buffer(product(this%pw_info%pw_grid%npts)))
618 ! collect from the processes at the IO process
619 DO i_proc = 0, this%para_env%num_pe - 1
620 length = product(this%npts_pproc(:, i_proc))
621 offset = this%lb_pproc(i_proc)*product(npts(2:)) + 1
622 buffer_p => buffer(offset:offset + length - 1)
623 IF (i_proc /= this%para_env%source) THEN
624 i = i_proc
625 CALL this%para_env%recv(buffer_p, i, tag)
626 ELSE
627 buffer_p = buffer_loc
628 END IF
629 END DO
630 ! send the density
631 CALL mcl_send(buffer, SIZE(buffer), mcl_data, this%mcl_server)
632 END IF
633
634 CALL timestop(handle)
635
636 END SUBROUTINE send_density
637
638! **************************************************************************************************
639!> \brief Send positions of all atoms to the server
640!> \param this ...
641! **************************************************************************************************
642 SUBROUTINE send_positions(this)
643 CLASS(mimic_communicator_type), INTENT(INOUT) :: this
644
645 CHARACTER(LEN=*), PARAMETER :: routineN = modulen//':send_positions'
646
647 REAL(dp), DIMENSION(:, :), ALLOCATABLE :: buffer
648 INTEGER :: handle, i_atom
649
650 CALL timeset(routinen, handle)
651
652 ALLOCATE (buffer(3, this%n_atoms))
653 DO i_atom = 1, this%n_atoms
654 buffer(:, i_atom) = this%atoms%els(i_atom)%r
655 END DO
656 CALL mcl_send(buffer, SIZE(buffer), mcl_data, this%mcl_server)
657
658 CALL timestop(handle)
659
660 END SUBROUTINE send_positions
661
662! **************************************************************************************************
663!> \brief Receive positions of all atoms from the server
664!> \param this ...
665! **************************************************************************************************
666 SUBROUTINE receive_positions(this)
667 CLASS(mimic_communicator_type), INTENT(INOUT) :: this
668
669 CHARACTER(LEN=*), PARAMETER :: routineN = modulen//':receive_positions'
670
671 REAL(dp), DIMENSION(:, :), ALLOCATABLE :: buffer
672 INTEGER :: handle, i_atom
673
674 CALL timeset(routinen, handle)
675
676 ALLOCATE (buffer(3, this%n_atoms))
677 CALL mcl_receive(buffer, SIZE(buffer), mcl_data, this%mcl_server)
678 CALL this%para_env%bcast(buffer)
679 DO i_atom = 1, this%n_atoms
680 this%atoms%els(i_atom)%r = buffer(:, i_atom)
681 END DO
682
683 CALL timestop(handle)
684
685 END SUBROUTINE receive_positions
686
687! **************************************************************************************************
688!> \brief Send QM forces of all atoms to the server
689!> \param this ...
690! **************************************************************************************************
691 SUBROUTINE send_forces(this)
692 CLASS(mimic_communicator_type), INTENT(INOUT) :: this
693
694 CHARACTER(LEN=*), PARAMETER :: routineN = modulen//':send_forces'
695
696 REAL(dp), DIMENSION(:, :), ALLOCATABLE :: buffer
697 INTEGER :: handle, i_atom
698
699 CALL timeset(routinen, handle)
700
701 ALLOCATE (buffer(3, this%n_atoms))
702 DO i_atom = 1, this%n_atoms
703 buffer(:, i_atom) = this%atoms%els(i_atom)%f
704 END DO
705 CALL mcl_send(buffer, SIZE(buffer), mcl_data, this%mcl_server)
706
707 CALL timestop(handle)
708
709 END SUBROUTINE send_forces
710
711END MODULE mimic_communicator
represent a simple array based list of the given type
Define the atomic kind types and their sub types.
subroutine, public get_atomic_kind(atomic_kind, fist_potential, element_symbol, name, mass, kind_number, natom, atom_list, rcov, rvdw, z, qeff, apol, cpol, mm_radius, shell, shell_active, damping)
Get attributes of an atomic kind.
Defines control structures, which contain the parameters and the settings for the DFT-based calculati...
set of type/routines to handle the storage of results in force_envs
set of type/routines to handle the storage of results in force_envs
types that represent a subsys, i.e. a part of the system
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
unit conversion facility
Definition cp_units.F:30
real(kind=dp) function, public cp_unit_from_cp2k(value, unit_str, defaults, power)
converts from the internal cp2k units to the given unit
Definition cp_units.F:1178
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, ipi_env)
returns various attributes about the force environment
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
Wrapper module for MiMiC Communication Library (MCL) routines.
Definition mcl_api.F:15
subroutine, public mcl_finalize()
Definition mcl_api.F:76
subroutine, public mcl_get_program_id(id)
Definition mcl_api.F:86
subroutine, public mcl_get_api_version(version)
Definition mcl_api.F:80
Wrapper module for MiMiC Communication Library (MCL) request labels.
integer, parameter, public mcl_request
integer, parameter, public mcl_data
integer, parameter, public mcl_runtype_qm_rs_grid
integer, parameter, public mcl_length
Interface to the message passing library MPI.
Module containing a MiMiC communicator class.
subroutine initialize(this, force_env)
Initialize the communicator by loading data and saving pointers to relevant data.
represent a simple array based list of the given type
container for various plainwaves related things
subroutine, public pw_env_get(pw_env, pw_pools, cube_info, gridlevel_info, auxbas_pw_pool, auxbas_grid, auxbas_rs_desc, auxbas_rs_grid, rs_descs, rs_grids, xc_pw_pool, vdw_pw_pool, poisson_env, interp_section)
returns the various attributes of the pw env
Manages a pool of grids (to be used for example as tmp objects), but can also be used to instantiate ...
subroutine, public get_qs_env(qs_env, atomic_kind_set, qs_kind_set, cell, super_cell, cell_ref, use_ref_cell, kpoints, dft_control, mos, sab_orb, sab_all, qmmm, qmmm_periodic, mimic, sac_ae, sac_ppl, sac_lri, sap_ppnl, sab_vdw, sab_scp, sap_oce, sab_lrc, sab_se, sab_xtbe, sab_tbe, sab_core, sab_xb, sab_xtb_pp, sab_xtb_nonbond, sab_almo, sab_kp, sab_kp_nosym, sab_cneo, particle_set, energy, force, matrix_h, matrix_h_im, matrix_ks, matrix_ks_im, matrix_vxc, run_rtp, rtp, matrix_h_kp, matrix_h_im_kp, matrix_ks_kp, matrix_ks_im_kp, matrix_vxc_kp, kinetic_kp, matrix_s_kp, matrix_w_kp, matrix_s_ri_aux_kp, matrix_s, matrix_s_ri_aux, matrix_w, matrix_p_mp2, matrix_p_mp2_admm, rho, rho_xc, pw_env, ewald_env, ewald_pw, active_space, mpools, input, para_env, blacs_env, scf_control, rel_control, kinetic, qs_charges, vppl, rho_core, rho_nlcc, rho_nlcc_g, ks_env, ks_qmmm_env, wf_history, scf_env, local_particles, local_molecules, distribution_2d, dbcsr_dist, molecule_kind_set, molecule_set, subsys, cp_subsys, oce, local_rho_set, rho_atom_set, task_list, task_list_soft, rho0_atom_set, rho0_mpole, rhoz_set, rhoz_cneo_set, ecoul_1c, rho0_s_rs, rho0_s_gs, rhoz_cneo_s_rs, rhoz_cneo_s_gs, do_kpoints, has_unit_metric, requires_mo_derivs, mo_derivs, mo_loc_history, nkind, natom, nelectron_total, nelectron_spin, efield, neighbor_list_id, linres_control, xas_env, virial, cp_ddapc_env, cp_ddapc_ewald, outer_scf_history, outer_scf_ihistory, x_data, et_coupling, dftb_potential, results, se_taper, se_store_int_env, se_nddo_mpole, se_nonbond_env, admm_env, lri_env, lri_density, exstate_env, ec_env, harris_env, dispersion_env, gcp_env, vee, rho_external, external_vxc, mask, mp2_env, bs_env, kg_env, wanniercentres, atprop, ls_scf_env, do_transport, transport_env, v_hartree_rspace, s_mstruct_changed, rho_changed, potential_changed, forces_up_to_date, mscfg_env, almo_scf_env, gradient_history, variable_history, embed_pot, spin_embed_pot, polar_env, mos_last_converged, eeq, rhs, do_rixs, tb_tblite)
Get the QUICKSTEP environment.
subroutine, public set_qs_env(qs_env, super_cell, mos, qmmm, qmmm_periodic, mimic, ewald_env, ewald_pw, mpools, rho_external, external_vxc, mask, scf_control, rel_control, qs_charges, ks_env, ks_qmmm_env, wf_history, scf_env, active_space, input, oce, rho_atom_set, rho0_atom_set, rho0_mpole, run_rtp, rtp, rhoz_set, rhoz_tot, ecoul_1c, has_unit_metric, requires_mo_derivs, mo_derivs, mo_loc_history, efield, rhoz_cneo_set, linres_control, xas_env, cp_ddapc_env, cp_ddapc_ewald, outer_scf_history, outer_scf_ihistory, x_data, et_coupling, dftb_potential, se_taper, se_store_int_env, se_nddo_mpole, se_nonbond_env, admm_env, ls_scf_env, do_transport, transport_env, lri_env, lri_density, exstate_env, ec_env, dispersion_env, harris_env, gcp_env, mp2_env, bs_env, kg_env, force, kpoints, wanniercentres, almo_scf_env, gradient_history, variable_history, embed_pot, spin_embed_pot, polar_env, mos_last_converged, eeq, rhs, do_rixs, tb_tblite)
Set the QUICKSTEP environment.
Define the quickstep kind type and their sub types.
subroutine, public get_qs_kind(qs_kind, basis_set, basis_type, ncgf, nsgf, all_potential, tnadd_potential, gth_potential, sgp_potential, upf_potential, cneo_potential, se_parameter, dftb_parameter, xtb_parameter, dftb3_param, zatom, zeff, elec_conf, mao, lmax_dftb, alpha_core_charge, ccore_charge, core_charge, core_charge_radius, paw_proj_set, paw_atom, hard_radius, hard0_radius, max_rad_local, covalent_radius, vdw_radius, gpw_type_forced, harmonics, max_iso_not0, max_s_harm, grid_atom, ngrid_ang, ngrid_rad, lmax_rho0, dft_plus_u_atom, l_of_dft_plus_u, n_of_dft_plus_u, u_minus_j, u_of_dft_plus_u, j_of_dft_plus_u, alpha_of_dft_plus_u, beta_of_dft_plus_u, j0_of_dft_plus_u, occupation_of_dft_plus_u, dispersion, bs_occupation, magnetization, no_optimize, addel, laddel, naddel, orbitals, max_scf, eps_scf, smear, u_ramping, u_minus_j_target, eps_u_ramping, init_u_ramping_each_scf, reltmat, ghost, monovalent, floating, name, element_symbol, pao_basis_size, pao_model_file, pao_potentials, pao_descriptors, nelec)
Get attributes of an atomic kind.
subroutine, public set_ks_env(ks_env, v_hartree_rspace, s_mstruct_changed, rho_changed, potential_changed, forces_up_to_date, complex_ks, matrix_h, matrix_h_im, matrix_ks, matrix_ks_im, matrix_vxc, kinetic, matrix_s, matrix_s_ri_aux, matrix_w, matrix_p_mp2, matrix_p_mp2_admm, matrix_h_kp, matrix_h_im_kp, matrix_ks_kp, matrix_vxc_kp, kinetic_kp, matrix_s_kp, matrix_w_kp, matrix_s_ri_aux_kp, matrix_ks_im_kp, vppl, rho_core, rho_nlcc, rho_nlcc_g, vee, neighbor_list_id, kpoints, sab_orb, sab_all, sac_ae, sac_ppl, sac_lri, sap_ppnl, sap_oce, sab_lrc, sab_se, sab_xtbe, sab_tbe, sab_core, sab_xb, sab_xtb_pp, sab_xtb_nonbond, sab_vdw, sab_scp, sab_almo, sab_kp, sab_kp_nosym, sab_cneo, task_list, task_list_soft, subsys, dft_control, dbcsr_dist, distribution_2d, pw_env, para_env, blacs_env)
...
superstucture that hold various representations of the density and keeps track of which ones are vali...
subroutine, public qs_rho_get(rho_struct, rho_ao, rho_ao_im, rho_ao_kp, rho_ao_im_kp, rho_r, drho_r, rho_g, drho_g, tau_r, tau_g, rho_r_valid, drho_r_valid, rho_g_valid, drho_g_valid, tau_r_valid, tau_g_valid, tot_rho_r, tot_rho_g, rho_r_sccs, soft_valid, complex_rho_ao)
returns info about the density described by this object. If some representation is not available an e...
contains arbitrary information which need to be stored
represents a system: atoms, molecules, their pos,vel,...
wrapper to abstract the force evaluation of the various methods
stores all the informations relevant to an mpi environment
MiMiC communicator class that facilitates MiMiC client-server data exchange.
contained for different pw related things
Manages a pool of grids (to be used for example as tmp objects), but can also be used to instantiate ...
Provides all information about a quickstep kind.
calculation environment to calculate the ks matrix, holds all the needed vars. assumes that the core ...
keeps the density in various representations, keeping track of which ones are valid.