TABLE OF CONTENTS


ABINIT/functionals_pwscf.F90 [ Modules ]

[ Top ] [ Modules ]

NAME

  functionals_pwscf

FUNCTION

 This module contains data defining the DFT functional in use
 and a number of functions and subroutines to manage them.
 Data are PRIVATE and are accessed and set only by function calls.
 Basic drivers to compute XC quantities are also included.

 imported into abinit by MJV 20/6/2009

COPYRIGHT

 Copyright (C) 2004 PWSCF group
 This file is distributed under the terms of the
 GNU General Public License. See the file `License'
 in the root directory of the present distribution,
 or http://www.gnu.org/copyleft/gpl.txt .

SOURCE

 24 !
 25 !-------------------------------------------------------------------
 26 
 27 #if defined HAVE_CONFIG_H
 28 #include "config.h"
 29 #endif
 30 
 31 module funct_pwscf
 32 !-------------------------------------------------------------------
 33 !  
 34 !  setting routines:   set_dft_from_name (previously which_dft)
 35 !                      set_dft_from_indices
 36 !                      enforce_input_dft
 37 !                      start_exx
 38 !                      stop_exx
 39 !  retrive functions:  get_dft_name
 40 !                      get_iexch
 41 !                      get_icorr
 42 !                      get_igcx
 43 !                      get_igcc
 44 !                      get_exx_fraction
 45 !                      dft_name
 46 !                      write_dft_name
 47 !  logical functions:  dft_is_gradient
 48 !                      dft_is_meta
 49 !                      dft_is_hybrid
 50 !                      exx_is_active
 51 !
 52 !  XC computation drivers: xc, xc_spin, gcxc, gcx_spin, gcc_spin, gcc_spin_more
 53 !  derivatives of XC computation drivers: dmxc, dmxc_spin, dmxc_nc
 54 !
 55   use flib_pwscf
 56 
 57   IMPLICIT NONE
 58   PRIVATE
 59   SAVE
 60   ! subroutines/functions managing dft name and indices
 61   PUBLIC  :: set_dft_from_indices, set_dft_from_name
 62   PUBLIC  :: enforce_input_dft, write_dft_name, dft_name
 63   PUBLIC  :: get_dft_name, get_iexch, get_icorr, get_igcx, get_igcc
 64   PUBLIC  :: dft_is_gradient, dft_is_meta, dft_is_hybrid
 65   ! additional subroutines/functions for hybrid functionale
 66   PUBLIC  :: start_exx, stop_exx, get_exx_fraction, exx_is_active
 67   !
 68   ! PRIVATE variables defining the DFT functional
 69   !
 70   PRIVATE :: dft, iexch, icorr, igcx, igcc
 71   PRIVATE :: discard_input_dft
 72   PRIVATE :: isgradient, ismeta, ishybrid
 73   PRIVATE :: exx_fraction, exx_started
 74   !PRIVATE :: dft_shortname
 75   !
 76   character (len=50) :: dft = 'not set'
 77   !character (len=4)  :: dft_shortname = ' '
 78   !
 79   ! dft is the exchange-correlation functional, described by
 80   ! any nonconflicting combination of the following keywords
 81   ! (case-insensitive):
 82   !
 83   ! Exchange:    "nox"    none                           iexch=0
 84   !              "sla"    Slater (alpha=2/3)             iexch=1 (default)
 85   !              "sl1"    Slater (alpha=1.0)             iexch=2
 86   !              "rxc"    Relativistic Slater            iexch=3
 87   !              "oep"    Optimized Effective Potential  iexch=4
 88   !              "hf"     Hartree-Fock                   iexch=5
 89   !              "pb0x"   PBE0                           iexch=6
 90   !
 91   ! Correlation: "noc"    none                           icorr=0
 92   !              "pz"     Perdew-Zunger                  icorr=1 (default)
 93   !              "vwn"    Vosko-Wilk-Nusair              icorr=2
 94   !              "lyp"    Lee-Yang-Parr                  icorr=3
 95   !              "pw"     Perdew-Wang                    icorr=4
 96   !              "wig"    Wigner                         icorr=5
 97   !              "hl"     Hedin-Lunqvist                 icorr=6
 98   !              "obz"    Ortiz-Ballone form for PZ      icorr=7
 99   !              "obw"    Ortiz-Ballone form for PW      icorr=8
100   !              "gl"     Gunnarson-Lunqvist             icorr=9
101   !
102   ! Gradient Correction on Exchange:
103   !              "nogx"   none                           igcx =0 (default)
104   !              "b88"    Becke88 (beta=0.0042)          igcx =1
105   !              "ggx"    Perdew-Wang 91                 igcx =2
106   !              "pbx"    Perdew-Burke-Ernzenhof exch    igcx =3
107   !              "rpb"    revised PBE by Zhang-Yang      igcx =4
108   !              "hcth"   Cambridge exch, Handy et al    igcx =5
109   !              "optx"   Handy's exchange functional    igcx =6
110   !              "meta"   meta-gga                       igcx =7
111   !              "pb0x"   PBE0                           igcx =8
112   !
113   ! Gradient Correction on Correlation:
114   !              "nogc"   none                           igcc =0 (default)
115   !              "p86"    Perdew86                       igcc =1
116   !              "ggc"    Perdew-Wang 91 corr.           igcc =2
117   !              "blyp"   Lee-Yang-Parr                  igcc =3
118   !              "pbc"    Perdew-Burke-Ernzenhof corr    igcc =4
119   !              "hcth"   Cambridge corr, Handy et al    igcc =5
120   !              "meta"   meta-gga                       igcc =6
121   !
122   ! Special cases (dft_shortnames):
123   !              "bp"   = "b88+p86"         = Becke-Perdew grad.corr.
124   !              "pw91" = "pw +ggx+ggc"     = PW91 (aka GGA)
125   !              "blyp" = "sla+b88+lyp+blyp"= BLYP
126   !              "pbe"  = "sla+pw+pbx+pbc"  = PBE
127   !              "revpbe"="sla+pw+rpb+pbc"  = revPBE (Zhang-Yang)
128   !              "hcth" = "nox+noc+hcth+hcth"=HCTH/120
129   !              "olyp" = "nox+lyp+optx+blyp" !!! UNTESTED !!!
130   !
131   ! References:
132   !              pz      J.P.Perdew and A.Zunger, PRB 23, 5048 (1981) [[cite:Perdew1981]]
133   !              vwn     S.H.Vosko, L.Wilk, M.Nusair, Can.J.Phys. 58,1200(1980) [[cite:Vosko1980]]
134   !              wig     E.P.Wigner, Trans. Faraday Soc. 34, 67 (1938) [[cite:Wigner1938]]
135   !              hl      L.Hedin and B.I.Lundqvist, J. Phys. C4, 2064 (1971) [[cite:Hedin1971]]
136   !              gl      O.Gunnarsson and B.I.Lundqvist, PRB 13, 4274 (1976) [[cite:Gunnarsson1976]]
137   !              pw      J.P.Perdew and Y.Wang, PRB 45, 13244 (1992) [[cite:Perdew1992a]]
138   !              obpz    G.Ortiz and P.Ballone, PRB 50, 1391 (1994) [[cite:Ortiz1994]]
139   !              obpw    as above
140   !              b88     A.D.Becke, PRA 38, 3098 (1988) [[cite:Becke1988]]
141   !              p86     J.P.Perdew, PRB 33, 8822 (1986) [[cite:Perdew1986]] 
142   !              pbe     J.P.Perdew, K.Burke, M.Ernzerhof, PRL 77, 3865 (1996) [[cite:Perdew1996]]
143   !              pw91    J.P.Perdew and Y. Wang, PRB 46, 6671 (1992) [[cite:Perdew1992]]
144   !              blyp    C.Lee, W.Yang, R.G.Parr, PRB 37, 785 (1988) [[cite:Lee1988]]
145   !              hcth    Hamprecht et al, JCP 109, 6264 (1998) [[cite:Hamprecht1998]]
146   !              olyp    Handy and Cohen, JCP 116, 5411 (2002) [[cite:Handy2002]]
147   !              revPBE  Zhang and Yang, PRL 80, 890 (1998) [[cite:Zhang1998]]
148   !              oep
149 
150   integer, parameter:: notset = -1
151   !
152   integer :: iexch = notset
153   integer :: icorr = notset
154   integer :: igcx  = notset
155   integer :: igcc  = notset
156   real(8):: exx_fraction = 0.0d0
157   logical :: isgradient  = .false.
158   logical :: ismeta      = .false.
159   logical :: ishybrid    = .false.
160   logical :: exx_started = .false.
161 
162   logical :: discard_input_dft = .false.
163   !
164   ! internal indices for exchange-correlation
165   !    iexch: type of exchange
166   !    icorr: type of correlation
167   !    igcx:  type of gradient correction on exchange
168   !    igcc:  type of gradient correction on correlation
169   !
170   !    ismeta: .TRUE. if gradient correction is of meta-gga type
171   !    ishybrid: .TRUE. if the xc finctional is an HF+DFT hybrid like
172   !              PBE0 or B3LYP or HF itself
173   !
174   ! see comments above and routine "set_dft_from_name" below 
175   !
176   ! data
177   integer :: nxc, ncc, ngcx, ngcc
178   parameter (nxc = 7, ncc =10, ngcx = 9, ngcc = 7)
179   character (len=4) :: exc, corr
180   character (len=4) :: gradx, gradc
181   dimension exc (0:nxc), corr (0:ncc), gradx (0:ngcx), gradc (0: ngcc)
182 
183   data exc / 'NOX', 'SLA', 'SL1', 'RXC', 'OEP', 'HF', 'PB0X', 'B3LP' /
184   data corr / 'NOC', 'PZ', 'VWN', 'LYP', 'PW', 'WIG', 'HL', 'OBZ', &
185               'OBW', 'GL' , 'B3LP' /
186   data gradx / 'NOGX', 'B88', 'GGX', 'PBX',  'RPB', 'HCTH', 'OPTX', 'META', 'PB0X', 'B3LP'  /
187   data gradc / 'NOGC', 'P86', 'GGC', 'BLYP', 'PBC', 'HCTH', 'META', 'B3LP' /
188 
189 CONTAINS

functionals_pwscf/dft_is_gradient [ Functions ]

[ Top ] [ Functions ]

NAME

 dft_is_gradient

FUNCTION

INPUTS

OUTPUT

SOURCE

692   !-----------------------------------------------------------------------
693   function dft_is_gradient ()
694 
695      logical :: dft_is_gradient
696      dft_is_gradient = isgradient
697      return
698   end function dft_is_gradient

functionals_pwscf/dft_is_hybrid [ Functions ]

[ Top ] [ Functions ]

NAME

 dft_is_hybrid

FUNCTION

INPUTS

OUTPUT

SOURCE

734   !-----------------------------------------------------------------------
735   function dft_is_hybrid ()
736 
737      logical :: dft_is_hybrid
738      dft_is_hybrid = ishybrid
739      return
740   end function dft_is_hybrid

functionals_pwscf/dft_is_meta [ Functions ]

[ Top ] [ Functions ]

NAME

 dft_is_meta

FUNCTION

INPUTS

OUTPUT

SOURCE

713   !-----------------------------------------------------------------------
714   function dft_is_meta ()
715 
716      logical :: dft_is_meta
717      dft_is_meta = ismeta
718      return
719   end function dft_is_meta

functionals_pwscf/dft_name [ Functions ]

[ Top ] [ Functions ]

NAME

 dft_name

FUNCTION

 convert the four indices iexch, icorr, igcx, igcc
 into user-readable strings

INPUTS

OUTPUT

SOURCE

805   !---------------------------------------------------------------------
806   subroutine dft_name(iexch_, icorr_, igcx_, igcc_, longname_, shortname_)
807   !---------------------------------------------------------------------
808   implicit none
809   integer iexch_, icorr_, igcx_, igcc_
810   character (len=4) :: shortname_
811   character (len=20):: longname_
812   !
813   if (iexch_==1.and.igcx_==0.and.igcc_==0) then
814      shortname_ = corr(icorr_)
815   else if (iexch_==1.and.icorr_==3.and.igcx_==1.and.igcc_==3) then
816      shortname_ = 'BLYP'
817   else if (iexch_==1.and.icorr_==1.and.igcx_==1.and.igcc_==0) then
818      shortname_ = 'B88'
819   else if (iexch_==1.and.icorr_==1.and.igcx_==1.and.igcc_==1) then
820      shortname_ = 'BP'
821   else if (iexch_==1.and.icorr_==4.and.igcx_==2.and.igcc_==2) then
822      shortname_ = 'PW91'
823   else if (iexch_==1.and.icorr_==4.and.igcx_==3.and.igcc_==4) then
824      shortname_ = 'PBE'
825   else if (iexch_==6.and.icorr_==4.and.igcx_==8.and.igcc_==4) then
826      shortname_ = 'PBE0'
827   else
828      shortname_ = ' '
829   end if
830   write(longname_,'(4a5)') exc(iexch_),corr(icorr_),gradx(igcx_),gradc(igcc_)
831   
832   return
833 end subroutine dft_name

functionals_pwscf/enforce_input_dft [ Functions ]

[ Top ] [ Functions ]

NAME

 enforce_input_dft

FUNCTION

 translates a string containing the exchange-correlation name
 into internal indices and force any subsequent call to set_dft_from_name
 to return without changing them

INPUTS

OUTPUT

SOURCE

464   !-----------------------------------------------------------------------
465   subroutine enforce_input_dft (dft_)
466   !
467     use defs_basis, only : std_out,std_out_default
468     use flib_pwscf
469     implicit none
470     ! input
471     character(len=*) :: dft_
472     ! data
473 
474      call set_dft_from_name (dft_)
475      if (dft == 'not set') then
476        call errore('enforce_input_dft','cannot fix unset dft',1)
477      end if
478      discard_input_dft = .true.
479 
480      write(std_out,'(/,5x,a)') "!!! XC functional enforced from input :"
481      call write_dft_name
482      write(std_out,'(5x,a)') "!!! Any further DFT definition will be discarded"
483      write(std_out,'(5x,a)') "!!! Please, verify this is what you really want !"
484 
485      return
486   end subroutine enforce_input_dft

functionals_pwscf/exx_is_active [ Functions ]

[ Top ] [ Functions ]

NAME

 exx_is_active

FUNCTION

INPUTS

OUTPUT

SOURCE

547   function exx_is_active ()
548 
549      logical exx_is_active
550      exx_is_active = exx_started
551   end function exx_is_active

functionals_pwscf/get_dft_name [ Functions ]

[ Top ] [ Functions ]

NAME

 get_dft_name

FUNCTION

INPUTS

OUTPUT

SOURCE

671   !-----------------------------------------------------------------------
672   function get_dft_name ()
673 
674      character (len=50) :: get_dft_name
675      get_dft_name = dft
676      return
677   end function get_dft_name

functionals_pwscf/get_exx_fraction [ Functions ]

[ Top ] [ Functions ]

NAME

 get_exx_fraction

FUNCTION

INPUTS

OUTPUT

SOURCE

650   !-----------------------------------------------------------------------
651   function get_exx_fraction ()
652 
653      real(8):: get_exx_fraction
654      get_exx_fraction = exx_fraction
655      return
656   end function get_exx_fraction

functionals_pwscf/get_icorr [ Functions ]

[ Top ] [ Functions ]

NAME

 get_icorr

FUNCTION

INPUTS

OUTPUT

SOURCE

587   !-----------------------------------------------------------------------
588   function get_icorr ()
589 
590      integer get_icorr
591      get_icorr = icorr
592      return
593   end function get_icorr

functionals_pwscf/get_iexch [ Functions ]

[ Top ] [ Functions ]

NAME

 get_iexch

FUNCTION

INPUTS

OUTPUT

SOURCE

566   !-----------------------------------------------------------------------
567   function get_iexch ()
568 
569      integer get_iexch
570      get_iexch = iexch
571      return
572   end function get_iexch

functionals_pwscf/get_igcc [ Functions ]

[ Top ] [ Functions ]

NAME

 get_igcc

FUNCTION

INPUTS

OUTPUT

SOURCE

629   !-----------------------------------------------------------------------
630   function get_igcc ()
631 
632      integer get_igcc
633      get_igcc = igcc
634      return
635   end function get_igcc

functionals_pwscf/get_igcx [ Functions ]

[ Top ] [ Functions ]

NAME

 get_igcx

FUNCTION

INPUTS

OUTPUT

SOURCE

608   !-----------------------------------------------------------------------
609   function get_igcx ()
610 
611      integer get_igcx
612      get_igcx = igcx
613      return
614   end function get_igcx

functionals_pwscf/set_auxiliary_flags [ Functions ]

[ Top ] [ Functions ]

NAME

 set_auxiliary_flags

FUNCTION

 set logical flags describing the complexity of the xc functional
 define the fraction of exact exchange used by hybrid fuctionals

INPUTS

OUTPUT

SOURCE

400   !-----------------------------------------------------------------------
401   subroutine set_auxiliary_flags
402   !-----------------------------------------------------------------------
403 
404     use flib_pwscf
405     isgradient =  (igcx > 0) .or. (igcc > 0) 
406     ismeta     =  (igcx == 7) .or. (igcx == 6 )
407 
408     ! PBE0
409     IF ( iexch==6 .or. igcx==8 ) exx_fraction = 0.25d0
410     ! HF or OEP
411     IF ( iexch==4 .or. iexch==5 ) exx_fraction = 1.0d0
412     !B3LYP
413     IF ( matches( 'B3LP',dft ) ) exx_fraction = 0.2d0
414     ishybrid = ( exx_fraction /= 0.0d0 )
415 
416     return
417   end subroutine set_auxiliary_flags

functionals_pwscf/set_dft_from_indices [ Functions ]

[ Top ] [ Functions ]

NAME

 set_dft_from_indices

FUNCTION

INPUTS

OUTPUT

SOURCE

755   !-----------------------------------------------------------------------
756   subroutine set_dft_from_indices(iexch_,icorr_,igcx_,igcc_)
757 
758     use defs_basis, only : std_out,std_out_default
759     use flib_pwscf
760     implicit none
761      integer :: iexch_, icorr_, igcx_, igcc_
762      if ( discard_input_dft ) return
763      if (iexch == notset) iexch = iexch_
764      if (iexch /= iexch_) then
765         write(std_out,*) iexch, iexch_
766         call errore('set_dft',' conflicting values for iexch',1)
767      end if
768      if (icorr == notset) icorr = icorr_
769      if (icorr /= icorr_) then
770         write(std_out,*) icorr, icorr_
771         call errore('set_dft',' conflicting values for icorr',1)
772      end if
773      if (igcx  == notset) igcx = igcx_
774      if (igcx /= igcx_) then
775         write(std_out,*) igcx, igcx_
776         call errore('set_dft',' conflicting values for igcx',1)
777      end if
778      if (igcc  == notset) igcc = igcc_
779      if (igcc /= igcc_) then
780         write(std_out,*) igcc, igcc_
781         call errore('set_dft',' conflicting values for igcc',1)
782      end if
783      dft = exc (iexch) //'-'//corr (icorr) //'-'//gradx (igcx) //'-' &
784            &//gradc (igcc)
785      ! write(std_out,'(a)') dft
786      call set_auxiliary_flags
787      return
788   end subroutine set_dft_from_indices

functionals_pwscf/set_dft_from_name [ Functions ]

[ Top ] [ Functions ]

NAME

 set_dft_from_name

FUNCTION

 translates a string containing the exchange-correlation name
 into internal indices iexch, icorr, igcx, igcc

INPUTS

OUTPUT

SOURCE

206   !-----------------------------------------------------------------------
207   subroutine set_dft_from_name( dft_ )
208   !-----------------------------------------------------------------------
209 
210     use flib_pwscf
211     implicit none
212     ! input
213     character(len=*)               :: dft_
214     ! local
215     integer :: len, l, i
216     character (len=50):: dftout
217     !
218     !
219     ! if 
220     !
221     if ( discard_input_dft ) return
222     !
223     ! convert to uppercase
224     len = len_trim(dft_)
225     dftout = ' '
226     do l = 1, len
227        dftout (l:l) = capital (dft_(l:l) )
228     enddo
229 
230     !  exchange
231     iexch = notset
232     do i = 0, nxc
233        if (matches (exc (i), dftout) ) then
234          call set_dft_value (iexch, i)
235        end if
236     enddo
237 
238     !  correlation
239     icorr = notset
240     do i = 0, ncc
241        if (matches (corr (i), dftout) ) then
242          call set_dft_value (icorr, i)
243        end if
244     enddo
245 
246     !  gradient correction, exchange
247     igcx = notset
248     do i = 0, ngcx
249        if (matches (gradx (i), dftout) ) then
250          call set_dft_value (igcx, i)
251        end if
252     enddo
253 
254     !  gradient correction, correlation
255     igcc = notset
256     do i = 0, ngcc
257        if (matches (gradc (i), dftout) ) then
258          call set_dft_value (igcc, i)
259        end if
260     enddo
261 
262     ! special case : BLYP => B88 for gradient correction on exchange
263     if (matches ('BLYP', dftout) ) then
264       call set_dft_value (igcx, 1)
265     end if
266 
267     ! special case : revPBE
268     if (matches ('REVPBE', dftout) ) then
269        call set_dft_value (icorr,4)
270        call set_dft_value (igcx, 4)
271        call set_dft_value (igcc, 4)
272     else if (matches('RPBE',dftout)) then
273          call errore('set_dft_from_name', &
274      &   'RPBE (Hammer-Hansen-Norskov) not implemented (revPBE is)',1)
275    else if (matches ('PBE0', dftout) ) then
276     ! special case : PBE0
277        call set_dft_value (iexch,6)
278        call set_dft_value (icorr,4)
279        call set_dft_value (igcx, 8)
280        call set_dft_value (igcc, 4)
281    else if (matches ('PBE', dftout) ) then
282     ! special case : PBE
283        call set_dft_value (icorr,4)
284        call set_dft_value (igcx, 3)
285        call set_dft_value (igcc, 4)
286    endif
287 
288     if (matches ('PBC', dftout) ) then
289     ! special case : PBC  = PW + PBC 
290        call set_dft_value (icorr,4)
291        call set_dft_value (igcc, 4)
292     endif
293 
294     ! special case : BP = B88 + P86
295     if (matches ('BP', dftout) ) then
296        call set_dft_value (igcx, 1)
297        call set_dft_value (igcc, 1)
298     endif
299 
300     ! special case : PW91 = GGX + GGC
301     if (matches ('PW91', dftout) ) then
302        call set_dft_value (igcx, 2)
303        call set_dft_value (igcc, 2)
304     endif
305 
306     ! special case : HCTH already contains LDA exchange and correlation
307 
308     if (matches('HCTH',dftout)) then
309        call set_dft_value(iexch,0)
310        call set_dft_value(icorr,0)
311     end if
312 
313     ! special case : OPTX already contains LDA exchange
314      
315     if (matches('OPTX',dftout)) then
316        call set_dft_value(iexch,0)
317     end if
318 
319     ! special case : OLYP = OPTX + LYP
320 
321     if (matches('OLYP',dftout)) then
322        call set_dft_value(iexch,0)
323        call set_dft_value(icorr,3)
324        call set_dft_value(igcx,6)
325        call set_dft_value(igcc,3)
326     end if
327     !
328     ! ... special case : TPSS meta-GGA Exc
329     !
330     IF ( matches( 'TPSS', dftout ) ) THEN
331        !
332        CALL set_dft_value( iexch, 1 )
333        CALL set_dft_value( icorr, 4 )
334        CALL set_dft_value( igcx,  7 )
335        CALL set_dft_value( igcc,  6 )
336        !
337     END IF
338     !
339     ! ... special cases : OEP and HF need not GC part (nor LDA...)
340     !                     and include no correlation by default
341     !
342     IF ( matches( 'OEP', dftout ) .OR. matches( 'HF', dftout )) THEN
343        !
344        CALL set_dft_value( igcx,  0 )
345        if (icorr == notset) then
346          call set_dft_value (icorr, 0)
347        end if
348        !
349     END IF
350 
351 
352     if (igcx == 6) &
353          call errore('set_dft_from_name','OPTX untested! please test',-igcx)
354     ! Default value: Slater exchange
355     if (iexch == notset) then
356       call set_dft_value (iexch, 1)
357     end if
358 
359     ! Default value: Perdew-Zunger correlation
360     if (icorr == notset) then
361       call set_dft_value (icorr, 1)
362     end if
363 
364     ! Default value: no gradient correction on exchange
365     if (igcx == notset) then
366       call set_dft_value (igcx, 0)
367     end if
368 
369     ! Default value: no gradient correction on correlation
370     if (igcc == notset) then
371       call set_dft_value (igcc, 0)
372     end if
373 
374     dft = dftout
375 
376     dftout = exc (iexch) //'-'//corr (icorr) //'-'//gradx (igcx) //'-' &
377          &//gradc (igcc)
378 
379     call set_auxiliary_flags
380 
381     return
382   end subroutine set_dft_from_name

functionals_pwscf/set_dft_value [ Functions ]

[ Top ] [ Functions ]

NAME

 set_dft_value

FUNCTION

INPUTS

OUTPUT

SOURCE

432   !-----------------------------------------------------------------------
433   subroutine set_dft_value (m, i)
434   !-----------------------------------------------------------------------
435     use flib_pwscf
436     implicit none
437     integer :: m, i
438     ! local
439 
440     if ( m /= notset .and. m /= i) &
441          call errore ('set_dft_value', 'two conflicting matching values', 1)
442     m = i
443     return
444 
445   end subroutine set_dft_value

functionals_pwscf/start_exx [ Functions ]

[ Top ] [ Functions ]

NAME

 start_exx

FUNCTION

INPUTS

OUTPUT

SOURCE

502   subroutine start_exx 
503 
504     use flib_pwscf
505      if (.not. ishybrid) &
506         call errore('start_exx','dft is not hybrid, wrong call',1)
507      exx_started = .true.
508   end subroutine start_exx

functionals_pwscf/stop_exx [ Functions ]

[ Top ] [ Functions ]

NAME

 stop_exx

FUNCTION

INPUTS

OUTPUT

SOURCE

524   !-----------------------------------------------------------------------
525   subroutine stop_exx 
526 
527     use flib_pwscf
528      if (.not. ishybrid) &
529         call errore('stop_exx','dft is not hybrid, wrong call',1)
530      exx_started = .false.
531   end subroutine stop_exx

functionals_pwscf/write_dft_name [ Functions ]

[ Top ] [ Functions ]

NAME

 write_dft_name

FUNCTION

INPUTS

OUTPUT

SOURCE

849 subroutine write_dft_name
850 !-----------------------------------------------------------------------
851    use defs_basis, only : std_out,std_out_default
852    implicit none
853 
854    !write(std_out,'(5X,"Exchange-correlation      = ",A, &
855    !     &  " (",4I1,")")') TRIM( dft ), iexch, icorr, igcx, igcc
856 
857    write(std_out,'(5X,a,A,a,4I1,a)') "Exchange-correlation      = ", TRIM( dft ), " (", iexch, icorr, igcx, igcc, ")"
858    return
859 end subroutine write_dft_name
860 
861 
862 end module funct_pwscf