38      INTEGER(C_INT) FUNCTION libcp2kmw_setgrid(rx, ry, rz, ax, ay, az, bx, by, bz, cx, cy, cz) bind(C, NAME='libcp2kmw_setgrid')
 
   42         REAL(C_DOUBLE) :: ax, ay, az, bx, by, bz, cx, cy, cz
 
   75   SUBROUTINE maxwell_solver(maxwell_control, v_ee, sim_step, sim_time, scaling_factor)
 
   78      INTEGER, 
INTENT(IN)                                :: sim_step
 
   79      REAL(kind=
dp), 
INTENT(IN)                          :: sim_time
 
   80      REAL(kind=
dp), 
INTENT(IN)                          :: scaling_factor
 
   82#if defined(__LIBMAXWELL) 
   84      CHARACTER(len=*), 
PARAMETER                        :: routinen = 
'maxwell_solver' 
   86      INTEGER                                            :: handle, iounit, res, my_rank, num_pe, &
 
   87                                                            gid, master, tag, i, j, ip
 
   90      INTEGER, 
DIMENSION(3)                              :: lbounds, lbounds_local, npoints, &
 
   91                                                            npoints_local, ubounds, ubounds_local
 
   92      REAL(c_double), 
ALLOCATABLE, 
DIMENSION(:)          :: buffer
 
   94      mark_used(maxwell_control)
 
   99      CALL timeset(routinen, handle)
 
  104      my_rank = v_ee%pw_grid%para%group%mepos
 
  105      num_pe = v_ee%pw_grid%para%group%num_pe
 
  106      gid = v_ee%pw_grid%para%group
 
  109      lbounds = v_ee%pw_grid%bounds(1, :)
 
  110      ubounds = v_ee%pw_grid%bounds(2, :)
 
  111      npoints = v_ee%pw_grid%npts
 
  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
 
  117      ALLOCATE (buffer(lbounds(3):ubounds(3)))
 
  119      IF (my_rank == 0) 
THEN 
  123            WRITE (iounit, *) 
"MAXWELL| Called, step = ", sim_step, 
" time = ", sim_time
 
  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) &
 
  141         res = libcp2kmw_step(sim_step, sim_time)
 
  144            WRITE (iounit, *) 
"MAXWELL| Returned with value ", res
 
  145            WRITE (iounit, *) 
"MAXWELL| Distributing potential to MPI processes..." 
  151      CALL gid%bcast(buffer(lbounds(3):ubounds(3)), 0)
 
  154      DO i = lbounds(1), ubounds(1)
 
  155         DO j = lbounds(2), ubounds(2)
 
  158            IF ((lbounds_local(1) <= i) .AND. (i <= ubounds_local(1)) .AND. &
 
  159                (lbounds_local(2) <= j) .AND. (j <= ubounds_local(2))) 
THEN 
  161               v_ee%array(i, j, lbounds(3):ubounds(3)) = buffer(lbounds(3):ubounds(3))*scaling_factor
 
  168         WRITE (iounit, *) 
"MAXWELL| All done." 
  171      CALL timestop(handle)
 
  175      mark_used(maxwell_control)
 
  179      mark_used(scaling_factor)
 
  181      CALL cp_abort(__location__, &
 
  182                    "The Maxwell solver interface requires CP2k to be compiled & 
  183                     &with the -D__LIBMAXWELL preprocessor option.")