(git:374b731)
Loading...
Searching...
No Matches
maxwell_solver_interface.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 Interface to Maxwell equation solver
10!> \par History
11!> 11/2020 created [mbrehm]
12!> \author Martin Brehm
13! **************************************************************************************************
19 USE kinds, ONLY: dp
20 USE pw_types, ONLY: pw_r3d_rs_type
21 USE iso_c_binding, ONLY: c_int, c_double
22
23#include "./base/base_uses.f90"
24
25 IMPLICIT NONE
26
27 PRIVATE
28
29 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'maxwell_solver_interface'
30
31! *** Public subroutines ***
32 PUBLIC :: maxwell_solver
33
34#if defined(__LIBMAXWELL)
35
36 INTERFACE
37
38 INTEGER(C_INT) FUNCTION libcp2kmw_setgrid(rx, ry, rz, ax, ay, az, bx, by, bz, cx, cy, cz) bind(C, NAME='libcp2kmw_setgrid')
39 USE iso_c_binding, ONLY: c_int, c_double
40 IMPLICIT NONE
41 INTEGER(C_INT) :: rx, ry, rz
42 REAL(C_DOUBLE) :: ax, ay, az, bx, by, bz, cx, cy, cz
43 END FUNCTION libcp2kmw_setgrid
44
45 INTEGER(C_INT) FUNCTION libcp2kmw_step(step, t) bind(C, NAME='libcp2kmw_step')
46 USE iso_c_binding, ONLY: c_int, c_double
47 IMPLICIT NONE
48 INTEGER(C_INT) :: step
49 REAL(C_DOUBLE) :: t
50 END FUNCTION libcp2kmw_step
51
52 INTEGER(C_INT) FUNCTION libcp2kmw_getzrow(buf, px, py, zmin, zmax) bind(C, NAME='libcp2kmw_getzrow')
53 USE iso_c_binding, ONLY: c_int, c_double
54 IMPLICIT NONE
55 REAL(C_DOUBLE) :: buf(*)
56 INTEGER(C_INT) :: px, py, zmin, zmax
57 END FUNCTION libcp2kmw_getzrow
58
59 END INTERFACE
60
61#endif
62
63CONTAINS
64
65! **************************************************************************************************
66!> \brief Computes the external potential on the grid
67!> \param maxwell_control the Maxwell control section
68!> \param v_ee the realspace grid with the potential
69!> \param sim_step current simulation step
70!> \param sim_time current physical simulation time
71!> \param scaling_factor a factor to scale the potential with
72!> \date 12/2020
73!> \author Martin Brehm
74! **************************************************************************************************
75 SUBROUTINE maxwell_solver(maxwell_control, v_ee, sim_step, sim_time, scaling_factor)
76 TYPE(maxwell_control_type), INTENT(IN) :: maxwell_control
77 TYPE(pw_r3d_rs_type), POINTER :: v_ee
78 INTEGER, INTENT(IN) :: sim_step
79 REAL(kind=dp), INTENT(IN) :: sim_time
80 REAL(kind=dp), INTENT(IN) :: scaling_factor
81
82#if defined(__LIBMAXWELL)
83
84 CHARACTER(len=*), PARAMETER :: routinen = 'maxwell_solver'
85
86 INTEGER :: handle, iounit, res, my_rank, num_pe, &
87 gid, master, tag, i, j, ip
88 TYPE(cp_logger_type), POINTER :: logger
89
90 INTEGER, DIMENSION(3) :: lbounds, lbounds_local, npoints, &
91 npoints_local, ubounds, ubounds_local
92 REAL(c_double), ALLOCATABLE, DIMENSION(:) :: buffer
93
94 mark_used(maxwell_control)
95 mark_used(v_ee)
96 mark_used(sim_step)
97 mark_used(sim_time)
98
99 CALL timeset(routinen, handle)
100 NULLIFY (logger)
101 logger => cp_get_default_logger()
102 iounit = cp_logger_get_default_io_unit(logger)
103
104 my_rank = v_ee%pw_grid%para%my_pos
105 num_pe = v_ee%pw_grid%para%group_size
106 gid = v_ee%pw_grid%para%group
107 tag = 1
108
109 lbounds = v_ee%pw_grid%bounds(1, :)
110 ubounds = v_ee%pw_grid%bounds(2, :)
111 npoints = v_ee%pw_grid%npts
112
113 lbounds_local = v_ee%pw_grid%bounds_local(1, :)
114 ubounds_local = v_ee%pw_grid%bounds_local(2, :)
115 npoints_local = v_ee%pw_grid%npts_local
116
117 ALLOCATE (buffer(lbounds(3):ubounds(3)))
118
119 IF (my_rank == 0) THEN
120
121 IF (iounit > 0) THEN
122 WRITE (iounit, *) ""
123 WRITE (iounit, *) "MAXWELL| Called, step = ", sim_step, " time = ", sim_time
124 END IF
125
126 res = libcp2kmw_setgrid( &
127 ubounds(1) - lbounds(1) + 1, &
128 ubounds(2) - lbounds(2) + 1, &
129 ubounds(3) - lbounds(3) + 1, &
130 v_ee%pw_grid%dh(1, 1)*(ubounds(1) - lbounds(1) + 1), &
131 v_ee%pw_grid%dh(2, 1)*(ubounds(1) - lbounds(1) + 1), &
132 v_ee%pw_grid%dh(3, 1)*(ubounds(1) - lbounds(1) + 1), &
133 v_ee%pw_grid%dh(1, 2)*(ubounds(2) - lbounds(2) + 1), &
134 v_ee%pw_grid%dh(2, 2)*(ubounds(2) - lbounds(2) + 1), &
135 v_ee%pw_grid%dh(3, 2)*(ubounds(2) - lbounds(2) + 1), &
136 v_ee%pw_grid%dh(1, 3)*(ubounds(3) - lbounds(3) + 1), &
137 v_ee%pw_grid%dh(2, 3)*(ubounds(3) - lbounds(3) + 1), &
138 v_ee%pw_grid%dh(3, 3)*(ubounds(3) - lbounds(3) + 1) &
139 )
140
141 res = libcp2kmw_step(sim_step, sim_time)
142
143 IF (iounit > 0) THEN
144 WRITE (iounit, *) "MAXWELL| Returned with value ", res
145 WRITE (iounit, *) "MAXWELL| Distributing potential to MPI processes..."
146 END IF
147
148 END IF
149
150 ! The following code block is copied from src/pw/realspace_grid_cube.F
151 CALL gid%bcast(buffer(lbounds(3):ubounds(3)), 0)
152
153 !master sends all data to everyone
154 DO i = lbounds(1), ubounds(1)
155 DO j = lbounds(2), ubounds(2)
156
157 !only use data that is local to me - i.e. in slice of pencil I own
158 IF ((lbounds_local(1) <= i) .AND. (i <= ubounds_local(1)) .AND. &
159 (lbounds_local(2) <= j) .AND. (j <= ubounds_local(2))) THEN
160 !allow scaling of external potential values by factor 'scaling' (SCALING_FACTOR in input file)
161 v_ee%array(i, j, lbounds(3):ubounds(3)) = buffer(lbounds(3):ubounds(3))*scaling_factor
162 END IF
163
164 END DO
165 END DO
166
167 IF (iounit > 0) THEN
168 WRITE (iounit, *) "MAXWELL| All done."
169 END IF
170
171 CALL timestop(handle)
172
173#else
174
175 mark_used(maxwell_control)
176 mark_used(v_ee)
177 mark_used(sim_step)
178 mark_used(sim_time)
179 mark_used(scaling_factor)
180
181 CALL cp_abort(__location__, &
182 "The Maxwell solver interface requires CP2k to be compiled &
183 &with the -D__LIBMAXWELL preprocessor option.")
184
185#endif
186
187 END SUBROUTINE maxwell_solver
188
190
Defines control structures, which contain the parameters and the settings for the DFT-based calculati...
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...
type(cp_logger_type) function, pointer, public cp_get_default_logger()
returns the default logger
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
Interface to Maxwell equation solver.
subroutine, public maxwell_solver(maxwell_control, v_ee, sim_step, sim_time, scaling_factor)
Computes the external potential on the grid.
type of a logger, at the moment it contains just a print level starting at which level it should be l...