1!
2! Copyright (C) 2015 Quantum ESPRESSO group
3! This file is distributed under the terms of the
4! GNU General Public License. See the file `License'
5! in the root directory of the present distribution,
6! or http://www.gnu.org/copyleft/gpl.txt .
7!
8!----------------------------------------------------------------------------
9!----------------------------------------------------------------------------
10SUBROUTINE plugin_add_potential( v )
11!----------------------------------------------------------------------------
12! This routine is used to add the plugin potentials to the total electronic potential
13!
14USE io_global,        ONLY : stdout, ionode
15USE kinds,            ONLY : DP
16!
17USE fft_base,         ONLY : dfftp
18USE electrons_base,   ONLY : nspin
19!
20USE plugin_flags
21!
22! ***Environ MODULES BEGIN***
23! ***Environ MODULES END***
24!
25IMPLICIT NONE
26!
27REAL(DP), INTENT(INOUT) :: v(dfftp%nnr,nspin)
28!
29! ***Environ VARIABLES BEGIN***
30! ***Environ VARIABLES END***
31!
32! ***Environ CALLS BEGIN***
33! ***Environ CALLS END***
34
35END SUBROUTINE plugin_add_potential
36