1C> \ingroup nwxc
2C> @{
3C>
4C> \file nwxc_eval.F
5C> Routines that evaluate the current density functional
6C>
7C> The routines in this file evaluate the current density functional.
8C> They use a variety of other routines that implement specific
9C> functional terms. However, those other routines are not part of the
10C> API.
11C>
12C> @}
13C
14C> \ingroup nwxc_api
15C> @{
16C>
17C> \brief Evaluate the exchange-correlation energy and the 1st order
18C> partial derivatives
19C>
20C> Whenever density functionals are used we need the
21C> exchange-correlation energy as well as the 1st order derivatives.
22C> Hence there seemed little point in implementing a routine for the
23C> exchange-correlation energy only.
24C>
25C> A given density functional may consist of a variety of terms. The
26C> evaluation of the functional simply loops over all the terms and
27C> adds each contribution to the outputs. Therefore we first of all
28C> zero all the output variables, and subsequently add all the
29C> required terms.
30C>
31C> Experience has shown that for these kinds of routines it is
32C> essential to be precise about the arguments are. Hence we define
33C> them here is detail. First of all the inputs are:
34C>
35C> Rho (density)
36C> -------------
37C>
38C> Rho is the electron density. In closed shell cases the total
39C> electron density is used, in open shell cases the \f$\alpha\f$-electron
40C> and \f$\beta\f$-electron densities are used. The density is defined as
41C> \f{eqnarray*}{
42C>   \rho^\alpha(\vec{r})
43C>   &=& \sum_{i \in \{occupied\}}{\;}^\alpha\phi^*_i(\vec{r})\;^\alpha\phi_i(\vec{r}) \\\\
44C>   &=& \sum_{\mu\nu}\chi_\mu(\vec{r})D^\alpha_{\mu\nu}\chi_\nu(\vec{r}) \\\\
45C>   \rho^\beta(\vec{r})
46C>   &=& \sum_{i \in \{occupied\}}{\;}^\beta\phi^*_i(\vec{r})\;^\beta\phi_i(\vec{r}) \\\\
47C>   &=& \sum_{\mu\nu}\chi_\mu(\vec{r})D^\beta_{\mu\nu}\chi_\nu(\vec{r}) \\\\
48C>   \rho^t(\vec{r}) &=& \rho^\alpha(\vec{r})+\rho^\beta(\vec{r})
49C> \f}
50C> where \f$ D^\alpha \f$ and \f$ D^\beta \f$ are the \f$\alpha\f$- and
51C> \f$\beta\f$-electron density matrices, the functions \f$^\alpha\phi\f$ and
52C> \f$^\beta\phi\f$ are spin-orbitals.
53C>
54C> Gamma (density gradient)
55C> ------------------------
56C>
57C> Gamma is the norm of the density gradient squared. In closed shell cases
58C> norm of the gradient of the total electron density squared is used. In open
59C> shell cases the various spin components are used. The different components
60C> are defined as:
61C> \f{eqnarray*}{
62C>   \gamma^{\alpha\alpha}(\vec{r})
63C>   &=& \nabla\rho^\alpha(\vec{r})\cdot\nabla\rho^\alpha(\vec{r}) \\\\
64C>   \gamma^{\alpha\beta}(\vec{r})
65C>   &=& \nabla\rho^\alpha(\vec{r})\cdot\nabla\rho^\beta(\vec{r}) \\\\
66C>   \gamma^{\beta\beta}(\vec{r})
67C>   &=& \nabla\rho^\beta(\vec{r})\cdot\nabla\rho^\beta(\vec{r}) \\\\
68C>   \gamma^{tt}(\vec{r})
69C>   &=& \gamma^{\alpha\alpha}(\vec{r})+\gamma^{\beta\beta}(\vec{r})
70C>    +  2\gamma^{\alpha\beta}(\vec{r})
71C> \f}
72C> In the above the gradient of the density for one spin channel is of course
73C> \f{eqnarray*}{
74C>    \nabla\rho^\sigma(\vec{r})
75C>    &=& \sum_{\mu\nu}\left\{
76C>    \left(\nabla\chi_\mu(\vec{r})\right)D^\sigma_{\mu\nu}\chi_\nu(\vec{r})+
77C>    \chi_\mu(\vec{r})D^\sigma_{\mu\nu}\left(\nabla\chi_\nu(\vec{r})\right)
78C>    \right\}
79C> \f}
80C>
81C> Tau (kinetic energy density)
82C> ----------------------------
83C>
84C> Tau is the kinetic energy density which encapsulates 2nd derivative
85C> information about the electron density. This quantity is defined
86C> as:
87C> \f{eqnarray*}{
88C>   \tau^\sigma(\vec{r})
89C>   &=& \frac{1}{2}\sum_{i\in\{occupied\}}|\nabla\phi_i(\vec{r})|^2
90C> \f}
91C>
92C> Next the outputs are:
93C>
94C> The functional
95C> --------------
96C>
97C> The exchange-correlation energy at every point, in general terms defined
98C> as:
99C> \f{eqnarray*}{
100C>   f &=&
101C>   f\left(\rho^\alpha,\rho^\beta,\gamma^{\alpha\alpha},\gamma^{\alpha\beta},
102C>          \gamma^{\beta\beta},\tau^\alpha,\tau^\beta\right)
103C> \f}
104C>
105C> The derivatives of \f$f\f$ with respect to the density
106C> ------------------------------------------------------
107C>
108C> The derivative of the exchange-correlation energy with respect to the
109C> electron density (`dfdr`), defined as:
110C> \f{eqnarray*}{
111C>   \frac{\mathrm{d}f}{\mathrm{d}\rho^\alpha} \\\\
112C>   \frac{\mathrm{d}f}{\mathrm{d}\rho^\beta}
113C> \f}
114C>
115C> The derivatives of \f$f\f$ with respect to the density gradient
116C> ---------------------------------------------------------------
117C>
118C> The routine evaluates the following derivatives related to the density
119C> gradients (`dfdg`):
120C> \f{eqnarray*}{
121C>    \frac{\mathrm{d}f}{\mathrm{d}\gamma^{\alpha\alpha}} \\\\
122C>    \frac{\mathrm{d}f}{\mathrm{d}\gamma^{\alpha\beta}} \\\\
123C>    \frac{\mathrm{d}f}{\mathrm{d}\gamma^{\beta\beta}}
124C> \f}
125C>
126C> The derivatives of \f$f\f$ with respect to the kinetic energy density
127C> ---------------------------------------------------------------------
128C>
129C> The routine evaluates the following derivatives related to the kinetic
130C> energy density (`dfdt`):
131C> \f{eqnarray*}{
132C>   \frac{\mathrm{d}f}{\mathrm{d}\tau^{\alpha}} \\\\
133C>   \frac{\mathrm{d}f}{\mathrm{d}\tau^{\beta}}
134C> \f}
135C> where we define the kinetic energy density as
136C> \f{eqnarray*}{
137C>   \tau_\sigma &=& \sum_i \langle\phi_i^\sigma|\nabla^2|\phi_i^\sigma\rangle
138C> \f}
139C> I.e. we assume the factor \f$1/2\f$ to be absorbed into the functional.
140C>
141C> Conversions
142C> -----------
143C>
144C> This routine assumes that the functional is defined in terms of one
145C> particular set of quantities. In practice there are a number of different
146C> conventions that may be used and that are all equally valid. For example
147C> we have described the functional in terms of the \f$\alpha\f$- and
148C> \f$\beta\f$-electron density. However, the functional could also be defined
149C> in terms of the total- and spin-densities. There are a number of these
150C> equally valid representations that can be used. This leads to the question
151C> how quantities from one representation can be expressed in terms of those of
152C> another representation. Here we will present a number of these conversions
153C> that we have encountered and worked out.
154C>
155C> Converting between the norm of gradient squared and the norm
156C> ------------------------------------------------------------
157C>
158C> In the Gaussian basis set DFT code in NWChem the functional is differentiated
159C> with respect to the norm of the gradient squared. In the planewave codes
160C> by contrast the norm of the gradient is used. Hence we need to be able to
161C> convert the derivatives from one representation to another. Some of these
162C> conversions are simple, for example:
163C> \f{eqnarray*}{
164C>   \frac{\partial f}{\partial |\gamma^{\alpha\alpha}|}
165C>   &=&
166C>   \frac{\partial f}{\partial \gamma^{\alpha\alpha}}
167C>   \frac{\partial \gamma^{\alpha\alpha}}{\partial |\gamma^{\alpha\alpha}|} \\\\
168C>   \frac{\partial f}{\partial |\gamma^{\alpha\alpha}|}
169C>   &=&
170C>   \frac{\partial f}{\partial \gamma^{\alpha\alpha}}
171C>   \frac{\partial |\gamma^{\alpha\alpha}|^2}{\partial |\gamma^{\alpha\alpha}|} \\\\
172C>   \frac{\partial f}{\partial |\gamma^{\alpha\alpha}|}
173C>   &=& 2
174C>   \frac{\partial f}{\partial \gamma^{\alpha\alpha}}
175C>   |\gamma^{\alpha\alpha}|
176C> \f}
177C> Similarly we have for the \f$\gamma^{\beta\beta}\f$ component:
178C> \f{eqnarray*}{
179C>   \frac{\partial f}{\partial |\gamma^{\beta\beta}|}
180C>   &=& 2
181C>   \frac{\partial f}{\partial \gamma^{\beta\beta}}
182C>   |\gamma^{\beta\beta}|
183C> \f}
184C> To work out how to convert
185C> between these representations we start by considering the functional as
186C> a functional of the density matrices. Next we express the functional in
187C> terms of the desired quantities
188C> \f{eqnarray*}{
189C>   f\left(D^\alpha,D^\beta\right)
190C>   &=& f\left(\gamma^{\alpha\alpha}(D^\alpha),\gamma^{\beta\beta}(D^\beta),
191C>             \gamma^{\alpha\beta}(D^\alpha,D^\beta)\right) \\\\\
192C>   &=& f\left(|\gamma^{\alpha\alpha}(D^\alpha)|,
193C>              |\gamma^{\beta\beta}(D^\beta)|,
194C>              |\gamma^{tt}(D^\alpha,D^\beta)|\right) \\\\\
195C> \f}
196C> Because of the equalities we know that the derivatives with respect to a
197C> particular property also have to equate to eachother as, for example
198C> \f{eqnarray*}{
199C>   \frac{\mathrm{d} f\left(\gamma^{\alpha\alpha},
200C>         \gamma^{\beta\beta},
201C>         \gamma^{\alpha\beta}\right)}{\mathrm{d}\gamma^{\alpha\alpha}}
202C>   &=&
203C>   \frac{\mathrm{d} f\left(|\gamma^{\alpha\alpha}|,
204C>         |\gamma^{\beta\beta}|,
205C>         |\gamma^{tt}|\right)}{\mathrm{d}\gamma^{\alpha\alpha}} \\\\
206C>   \frac{\mathrm{d} f\left(\gamma^{\alpha\alpha},
207C>         \gamma^{\beta\beta},
208C>         \gamma^{\alpha\beta}\right)}{\mathrm{d}\gamma^{\beta\beta}}
209C>   &=&
210C>   \frac{\mathrm{d} f\left(|\gamma^{\alpha\alpha}|,
211C>         |\gamma^{\beta\beta}|,
212C>         |\gamma^{tt}|\right)}{\mathrm{d}\gamma^{\beta\beta}} \\\\
213C>   \frac{\mathrm{d} f\left(\gamma^{\alpha\alpha},
214C>         \gamma^{\beta\beta},
215C>         \gamma^{\alpha\beta}\right)}{\mathrm{d}\gamma^{\alpha\beta}}
216C>   &=&
217C>   \frac{\mathrm{d} f\left(|\gamma^{\alpha\alpha}|,
218C>         |\gamma^{\beta\beta}|,
219C>         |\gamma^{tt}|\right)}{\mathrm{d}\gamma^{\alpha\beta}} \\\\
220C> \f}
221C> On the left hand sides we have the quantities that this routine
222C> `nwxc_eval_df` calculates. Here we are particularly interested in the last
223C> equation.
224C> Working out the right hand sides we get:
225C> \f{eqnarray*}{
226C>   \frac{\mathrm{d} f\left(\gamma^{\alpha\alpha},
227C>         \gamma^{\beta\beta},
228C>         \gamma^{\alpha\beta}\right)}{\mathrm{d}\gamma^{\alpha\beta}}
229C>   &=&
230C>   \frac{\mathrm{d} f\left(|\gamma^{\alpha\alpha}|,
231C>         |\gamma^{\beta\beta}|,
232C>         |\gamma^{tt}|\right)}{\mathrm{d}|\gamma^{tt}|}
233C>   \frac{\mathrm{d}|\gamma^{tt}|}{\mathrm{d}\gamma^{\alpha\beta}}
234C> \f}
235C> Using the definition
236C> \f$|\gamma^{tt}|=(\gamma^{\alpha\alpha}+\gamma^{\beta\beta}+2\gamma^{\alpha\beta})^{1/2}\f$
237C> we can simplify this expression further to
238C> \f{eqnarray*}{
239C>   \frac{\mathrm{d} f\left(\gamma^{\alpha\alpha},
240C>         \gamma^{\beta\beta},
241C>         \gamma^{\alpha\beta}\right)}{\mathrm{d}\gamma^{\alpha\beta}}
242C>   &=&
243C>   \frac{\mathrm{d} f\left(|\gamma^{\alpha\alpha}|,
244C>         |\gamma^{\beta\beta}|,
245C>         |\gamma^{tt}|\right)}{\mathrm{d}|\gamma^{tt}|}
246C>   (\gamma^{tt})^{-1/2} \\\\
247C>   \frac{\mathrm{d} f\left(\gamma^{\alpha\alpha},
248C>         \gamma^{\beta\beta},
249C>         \gamma^{\alpha\beta}\right)}{\mathrm{d}\gamma^{\alpha\beta}}
250C>   |\gamma^{tt}|
251C>   &=&
252C>   \frac{\mathrm{d} f\left(|\gamma^{\alpha\alpha}|,
253C>         |\gamma^{\beta\beta}|,
254C>         |\gamma^{tt}|\right)}{\mathrm{d}|\gamma^{tt}|}
255C> \f}
256C> Interestingly this relationship does not depend on \f$\gamma^{\alpha\alpha}\f$
257C> or \f$\gamma^{\beta\beta}\f$ even though these quantities are contained
258C> in the norm of the total density gradient.
259C>
260C> \brief The functional and 1st order partial derivative evaluation
261C>
262      subroutine nwxc_eval_df(ipol,nq,rho,gamma,tau,f,dfdr,dfdg,dfdt)
263      implicit none
264#include "errquit.fh"
265#include "nwxcP.fh"
266C
267      integer ipol !< [Input] The number of spin channels
268      integer nq   !< [Input] The number of points
269C
270      double precision rho(nq,ipol)     !< [Input] Density
271      double precision gamma(nq,ipol+1) !< [Input] |Density gradient|^2
272      double precision tau(nq,ipol)     !< [Input] Kinetic energy
273                                        !< density
274C
275      double precision f(nq)           !< [Output] Energy
276      double precision dfdr(nq,ipol)   !< [Output] Derivative wrt rho
277      double precision dfdg(nq,ipol+1) !< [Output] Derivative wrt gamma
278      double precision dfdt(nq,ipol)   !< [Output] Derivative wrt tau
279C
280      if (nwxc_eval_method.eq.NWXCP_EVAL_AUTODF) then
281        call nwxca_eval_df(ipol,nq,rho,gamma,tau,f,dfdr,dfdg,dfdt)
282      else if (nwxc_eval_method.eq.NWXCP_EVAL_MAXIMA) then
283        call nwxcm_eval_df(ipol,nq,rho,gamma,tau,f,dfdr,dfdg,dfdt)
284      else
285        call errquit("nwxc_eval_df: unknown evaluator",nwxc_eval_method,
286     +               UERR)
287      endif
288      end
289C>
290C> @}
291C>
292C> \ingroup nwxc_priv
293C> @{
294C>
295C> \brief The functional and 1st order partial derivative evaluation with AD
296C>
297C> In actual fact this routine only sets up the memory and then calls the
298C> driver routine to drive the actual functional evaluation. The lack of
299C> a Fortran90 typecast drives this code structure.
300C>
301      subroutine nwxca_eval_df(ipol,nq,rho,gamma,tau,f,dfdr,dfdg,dfdt)
302#include "nwad.fh"
303      implicit none
304#include "errquit.fh"
305#include "mafdecls.fh"
306#include "nwxc_param.fh"
307      integer ipol !< [Input] The number of spin channels
308      integer nq   !< [Input] The number of points
309C
310      double precision rho(nq,ipol)     !< [Input] Density
311      double precision gamma(nq,ipol+1) !< [Input] |Density gradient|^2
312      double precision tau(nq,ipol)     !< [Input] Kinetic energy
313                                        !< density
314C
315      double precision f(nq)           !< [Output] Energy
316      double precision dfdr(nq,ipol)   !< [Output] Derivative wrt rho
317      double precision dfdg(nq,ipol+1) !< [Output] Derivative wrt gamma
318      double precision dfdt(nq,ipol)   !< [Output] Derivative wrt tau
319c
320      type(nwad_dble) :: memory_test_nwad(2)
321      double precision   memory_test_dble(2)
322      integer length
323      integer l_rho, k_rho !< Index for density
324      integer l_gam, k_gam !< Index for gradient
325      integer l_tau, k_tau !< Index for kinetic energy density
326      integer l_fun, k_fun !< Index for functional
327      integer ipl          !< Hack version of ipol
328c
329c     Work out how many double precision floating point words are needed
330c     to represent a single nwad_dble
331c
332      ipl = 2
333      length = (loc(memory_test_dble(2))-loc(memory_test_dble(1)))
334      length = (loc(memory_test_nwad(2))-loc(memory_test_nwad(1))
335     +          +length-1)/length
336      if(.not.ma_push_get(mt_dbl,length*nq*ipl,"nwad rho",l_rho,k_rho))
337     +  call errquit("nwxca_eval_df: cannot allocate nwad rho",
338     +    ma_sizeof(mt_dbl,length*nq*ipl,mt_byte),MA_ERR)
339      if(.not.ma_push_get(mt_dbl,length*nq*(ipl+1),"nwad gamma",
340     +                    l_gam,k_gam))
341     +  call errquit("nwxca_eval_df: cannot allocate nwad gamma",
342     +    ma_sizeof(mt_dbl,length*nq*(ipl+1),mt_byte),MA_ERR)
343      if(.not.ma_push_get(mt_dbl,length*nq*ipl,"nwad tau",l_tau,k_tau))
344     +  call errquit("nwxca_eval_df: cannot allocate nwad tau",
345     +    ma_sizeof(mt_dbl,length*nq*ipl,mt_byte),MA_ERR)
346      if(.not.ma_push_get(mt_dbl,length*nq,"nwad fun",l_fun,k_fun))
347     +  call errquit("nwxca_eval_df: cannot allocate nwad fun",
348     +    ma_sizeof(mt_dbl,length*nq,mt_byte),MA_ERR)
349c
350      call nwxc_eval_df_driver(ipol,nq,rho,gamma,tau,dbl_mb(k_rho),
351     +     dbl_mb(k_gam),dbl_mb(k_tau),dbl_mb(k_fun),f,
352     +     dfdr,dfdg,dfdt)
353c
354      if(.not.ma_pop_stack(l_fun)) call errquit(
355     +  "nwxca_eval_df: cannot deallocate nwad fun",0,MA_ERR)
356      if(.not.ma_pop_stack(l_tau)) call errquit(
357     +  "nwxca_eval_df: cannot deallocate nwad tau",0,MA_ERR)
358      if(.not.ma_pop_stack(l_gam)) call errquit(
359     +  "nwxca_eval_df: cannot deallocate nwad gam",0,MA_ERR)
360      if(.not.ma_pop_stack(l_rho)) call errquit(
361     +  "nwxca_eval_df: cannot deallocate nwad rho",0,MA_ERR)
362      end
363C>
364C> \brief Driver routine for the functional and first derivative evaluation
365C>
366C> This driver routine initializes the active variables and loops over the
367C> functional evaluations. Afterwards it interpolates the partial derivatives
368C> and returns the values of the functional and its 1st order partial
369C> derivatives. Obviously, interpolating the 1st order partial derivatives is
370C> particularly simply, but this scheme applies to all orders of derivatives.
371C> Due to different data types being required the memory for this routine
372C> needs to be allocated in the calling routine. Calling this subroutine
373C> effectively implements a typecast.
374C>
375C> One key point is that the implementation of the functionals assumes that
376C> the kinetic energy density is
377C> \f{eqnarray*}{
378C>   \tau_\sigma &=& \sum_i \langle\phi_i^\sigma|\nabla^2|\phi_i^\sigma\rangle
379C> \f}
380C> The NWChem code that generates the kinetic energy density computes the
381C> proper kinetic energy
382C> \f{eqnarray*}{
383C>   \tau_\sigma &=& \frac{1}{2}
384C>               \sum_i \langle\phi_i^\sigma|\nabla^2|\phi_i^\sigma\rangle
385C> \f}
386C> Hence we need to convert this quantity to what the functionals expect
387C> when we initialize the active variables (otherwise the conversion factor
388C> will affect the derivatives).
389C>
390      subroutine nwxc_eval_df_driver(ipol,nq,rho,gamma,tau,
391     +           nwad_rho,nwad_gam,nwad_tau,nwad_f,f,
392     +           dfdr,dfdg,dfdt)
393      use nwad1
394      implicit none
395#include "nwxc_param.fh"
396#include "errquit.fh"
397      integer ipol !< [Input] The number of spin channels
398      integer nq   !< [Input] The number of points
399C
400      double precision rho(nq,ipol) !< [Input] Density
401      double precision gamma(nq,3)  !< [Input] |Density gradient|^2
402      double precision tau(nq,ipol) !< [Input] Kinetic energy
403                                    !< density
404C
405      double precision f(nq)           !< [Output] Energy
406      double precision dfdr(nq,ipol)   !< [Output] Derivative wrt rho
407      double precision dfdg(nq,ipol+1) !< [Output] Derivative wrt gamma
408      double precision dfdt(nq,ipol)   !< [Output] Derivative wrt tau
409c
410      type(nwad_dble) :: nwad_rho(nq,2)
411      type(nwad_dble) :: nwad_gam(nq,3)
412      type(nwad_dble) :: nwad_tau(nq,2)
413      type(nwad_dble) :: nwad_f(nq)
414C
415      logical  nwxc_is_lda  !< Is the functional a GGA
416      logical  nwxc_is_gga  !< Is the functional a GGA
417      logical  nwxc_is_mgga !< Is the functional a meta-GGA
418      external nwxc_is_gga  !< Is the functional a GGA
419      external nwxc_is_mgga !< Is the functional a meta-GGA
420c
421      integer ix1           !< the variable rank
422      integer iv1           !< the variable label
423      integer nvar          !< the number of variables
424      double precision val  !< the functional (derivative) value
425      integer iq, ip
426c
427c     Scaling factors to convert
428c     - df/drho,
429c     - df/dgamma and
430c     - df/dtau
431c     to the quantities NWChem expects, i.e.
432c     - df/drhoa
433c     - df/dgammaaa+1/2*df/dgammaab
434c     - df/dta
435c
436      double precision sfac_ra  !< the closed shell RA scaling factor
437      double precision sfac_gaa !< the closed shell GAA scaling factor
438      double precision sfac_ta  !< the closed shell TA scaling factor
439      parameter(sfac_ra  = 1.0d0)
440      parameter(sfac_gaa = 2.0d0)
441      parameter(sfac_ta  = 1.0d0)
442c
443      if (ipol.eq.1) then
444        do iq = 1, nq
445          nwad_rho(iq,R_T) = set_rho_t(rho(iq,R_T))
446        enddo
447      else  ! ipol.eq.1
448        do iq = 1, nq
449          nwad_rho(iq,R_A) = set_rho_a(rho(iq,R_A))
450        enddo
451        do iq = 1, nq
452          nwad_rho(iq,R_B) = set_rho_b(rho(iq,R_B))
453        enddo
454      endif ! ipol.eq.1
455      if (nwxc_is_gga().or.nwxc_is_mgga()) then
456        if (ipol.eq.1) then
457          do iq = 1, nq
458            nwad_gam(iq,G_TT) = set_gamma_tt(gamma(iq,G_TT))
459          enddo
460        else  ! ipol.eq.1
461          do iq = 1, nq
462            nwad_gam(iq,G_AA) = set_gamma_aa(gamma(iq,G_AA))
463          enddo
464          do iq = 1, nq
465            nwad_gam(iq,G_AB) = set_gamma_ab(gamma(iq,G_AB))
466          enddo
467          do iq = 1, nq
468            nwad_gam(iq,G_BB) = set_gamma_bb(gamma(iq,G_BB))
469          enddo
470        endif ! ipol.eq.1
471      endif
472      if (nwxc_is_mgga()) then
473        if (ipol.eq.1) then
474          do iq = 1, nq
475            nwad_tau(iq,T_T) = set_tau_t(tau(iq,T_T))
476          enddo
477        else  ! ipol.eq.1
478          do iq = 1, nq
479            nwad_tau(iq,T_A) = set_tau_a(tau(iq,T_A))
480          enddo
481          do iq = 1, nq
482            nwad_tau(iq,T_B) = set_tau_b(tau(iq,T_B))
483          enddo
484        endif ! ipol.eq.1
485      endif
486c
487      call nwxc_eval_df_doit(ipol,nq,nwad_rho,nwad_gam,
488     +     nwad_tau,nwad_f)
489c
490c     Now unpack the results
491c
492      if (ipol.eq.1) then
493c
494c       Closed shell -> use scale factors
495c
496        do iq = 1, nq
497          f(iq) = get_val(nwad_f(iq))
498          nvar = get_nvar(nwad_f(iq))
499          do ix1 = 1, nvar
500            call get_d1(nwad_f(iq),ix1,val,iv1)
501            select case (iv1)
502              case (1)
503                dfdr(iq,D1_RA)  = val*sfac_ra
504              case (3)
505                dfdg(iq,D1_GAA) = val*sfac_gaa
506                dfdg(iq,D1_GAB) = 0.0d0
507              case (6)
508                dfdt(iq,D1_TA)  = val*sfac_ta
509              case default
510                call print(6,nwad_f(iq))
511                call errquit("nwxc_df_driver: illegal variable",
512     +                       iv1,UERR)
513            end select
514          enddo
515        enddo
516c
517      else
518c
519c       Unrestricted open shell -> plain unpacking
520c
521        do iq = 1, nq
522          f(iq) = get_val(nwad_f(iq))
523          nvar = get_nvar(nwad_f(iq))
524          do ix1 = 1, nvar
525            call get_d1(nwad_f(iq),ix1,val,iv1)
526            select case (iv1)
527              case (1)
528                dfdr(iq,D1_RA) = val
529              case (2)
530                dfdr(iq,D1_RB) = val
531              case (3)
532                dfdg(iq,D1_GAA) = val
533              case (4)
534                dfdg(iq,D1_GAB) = val
535              case (5)
536                dfdg(iq,D1_GBB) = val
537              case (6)
538                dfdt(iq,D1_TA) = val
539              case (7)
540                dfdt(iq,D1_TB) = val
541              case default
542                call print(6,nwad_f(iq))
543                call errquit("nwxc_df_driver: illegal variable",
544     +                       iv1,UERR)
545            end select
546          enddo
547        enddo
548c
549      endif
550c
551      end
552C>
553C> \brief Evaluate the functional and its first order derivatives
554C>
555C> Using automatic differentiation the functional and its first order
556C> derivatives are calculated for one direction. The loop over directions
557C> and the correct interpolation of the partial derivatives has to be handled
558C> in a driver routine.
559C>
560      subroutine nwxc_eval_df_doit(ipol,nq,rho,gamma,tau,f)
561      use nwad1
562      implicit none
563#include "intf_nwxc_c_p91.fh"
564#include "intf_nwxc_c_pw91lda.fh"
565c
566#include "intf_nwxc_x_p91.fh"
567c
568#include "nwxcP.fh"
569#include "nwxc_param.fh"
570      integer ipol !< [Input] The number of spin channels
571      integer nq   !< [Input] The number of points
572C
573      type(nwad_dble)::rho(nq,ipol)              !< [Input] Density
574      type(nwad_dble)::gamma(nq,ipol*(ipol+1)/2) !< [Input] |Density gradient|^2
575      type(nwad_dble)::tau(nq,ipol)              !< [Input] Kinetic energy
576                                                 !< density
577C
578      type(nwad_dble)::f(nq)           !< [Output] Energy
579!     double precision dfdr(nq,ipol)   !< [Output] Derivative wrt rho
580!     double precision dfdg(nq,ipol+1) !< [Output] Derivative wrt gamma
581!     double precision dfdt(nq,ipol)   !< [Output] Derivative wrt tau
582C
583      integer iq !< Counter over points
584      integer ip !< Counter over spin channels
585      integer it !< Counter of functional terms
586      integer n  !< Counter
587C
588      logical nwxc_is_gga  !< Is the functional a GGA
589      logical nwxc_is_mgga !< Is the functional a meta-GGA
590C
591      integer nd1r(2) !< The number of partial derivatives wrt rho as
592                      !< a function of ipol
593      integer nd1g(2) !< The number of partial derivatives wrt gamma as
594                      !< a function of ipol
595      integer nd1t(2) !< The number of partial derivatives wrt tau as
596                      !< a function of ipol
597C
598      external nwxc_k_dirac
599      external nwxc_k_becke88
600      external nwxc_k_pbe96
601c
602      integer max_param
603      parameter (max_param = 50)
604      double precision param(max_param)
605      double precision Axlsda
606      parameter (Axlsda = -0.9305257363491d0 )
607C
608      data nd1r / D1_RA,  D1_RB  /
609      data nd1g / D1_GAA, D1_GBB /
610      data nd1t / D1_TA,  D1_TB  /
611C
612      do iq = 1, nq
613        f(iq) = 0.0d0
614      enddo
615C
616      do it = 1, nwxc_num_f
617        select case (nwxc_ids(it))
618          case (NWXCP_X_SLATER)
619            call nwxc_x_dirac(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
620     +                        rho,f)
621          case (NWXCP_X_B86B)
622            call nwxc_x_b86b(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
623     +                       rho,gamma,f)
624          case (NWXCP_X_B88)
625            call nwxc_x_b88(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
626     +                      rho,gamma,f)
627          case (NWXCP_X_B97)
628            param(1) = 2.0d0
629            param(2) = 0.80940d+00
630            param(3) = 0.50730d+00
631            param(4) = 0.74810d+00
632            call nwxc_x_b97(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
633     +                      rho,gamma,f)
634          case (NWXCP_X_B97_1)
635            param(1) = 2.0d0
636            param(2) = 0.789518d+00
637            param(3) = 0.573805d+00
638            param(4) = 0.660975d+00
639            call nwxc_x_b97(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
640     +                      rho,gamma,f)
641          case (NWXCP_X_B97_2)
642            param(1) = 2.0d0
643            param(2) = 0.827642D+00
644            param(3) = 0.478400D-01
645            param(4) = 0.176125D+01
646            call nwxc_x_b97(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
647     +                      rho,gamma,f)
648          case (NWXCP_X_B97_3)
649            param(1) = 4.0d0
650            param(2) = 7.334648D-01
651            param(3) = 2.925270D-01
652            param(4) = 3.338789D+00
653            param(5) =-1.051158D+01
654            param(6) = 1.060907D+01
655            call nwxc_x_b97(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
656     +                      rho,gamma,f)
657          case (NWXCP_X_B97_D)
658            param(1) = 2.0d0
659            param(2) = 1.086620d+0
660            param(3) =-0.521270d+00
661            param(4) = 3.254290d+00
662            call nwxc_x_b97(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
663     +                      rho,gamma,f)
664          case (NWXCP_X_B97_G)
665            param(1) = 2.0d0
666            param(2) = 1.1068d0
667            param(3) =-0.8765d0
668            param(4) = 4.2639d0
669            call nwxc_x_b97(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
670     +                      rho,gamma,f)
671          case (NWXCP_X_B98)
672            param(1) = 2.0d0
673            param(2) = 0.790194d00
674            param(3) = 0.400271d00
675            param(4) = 0.832857d00
676            call nwxc_x_b97(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
677     +                      rho,gamma,f)
678          case (NWXCP_X_BNL)
679            param(1) = nwxc_cam_gamma
680            call nwxc_x_bnl(param,nwxc_rho_tol,ipol,nq,
681     +                      nwxc_wghts(it),rho,f)
682          case (NWXCP_X_CAMB88)
683            param(1) = nwxc_cam_alpha
684            param(2) = nwxc_cam_beta
685            param(3) = nwxc_cam_gamma
686            call nwxc_x_camb88(param,nwxc_rho_tol,ipol,nq,
687     +                         nwxc_wghts(it),rho,gamma,f)
688          case (NWXCP_X_CAMLSD)
689            param(1) = nwxc_cam_alpha
690            param(2) = nwxc_cam_beta
691            param(3) = nwxc_cam_gamma
692            call nwxc_x_camlsd(param,nwxc_rho_tol,ipol,nq,
693     +                         nwxc_wghts(it),rho,f)
694          case (NWXCP_X_CAMPBE)
695            param(1) = 0.8040d0
696            param(2) = 0.2195149727645171d0
697            param(3) = nwxc_cam_alpha
698            param(4) = nwxc_cam_beta
699            param(5) = nwxc_cam_gamma
700            call nwxc_x_campbe(param,nwxc_rho_tol,ipol,nq,
701     +                         nwxc_wghts(it),rho,gamma,f)
702          case (NWXCP_X_CAMREVPBE)
703            param(1) = 1.245d0
704            param(2) = 0.2195149727645171d0
705            param(3) = nwxc_cam_alpha
706            param(4) = nwxc_cam_beta
707            param(5) = nwxc_cam_gamma
708            call nwxc_x_campbe(param,nwxc_rho_tol,ipol,nq,
709     +                         nwxc_wghts(it),rho,gamma,f)
710          case (NWXCP_X_CAMRPBE)
711            param(1) = nwxc_cam_alpha
712            param(2) = nwxc_cam_beta
713            param(3) = nwxc_cam_gamma
714            call nwxc_x_camrpbe(param,nwxc_rho_tol,ipol,nq,
715     +                          nwxc_wghts(it),rho,gamma,f)
716          case (NWXCP_X_CAMS12G)
717            param(1) = 1.03323556d0
718            param(2) = 0.757d0
719            param(3) = 0.00417251d0
720            param(4) = 0.00115216d0
721            param(5) = 0.00706184d0
722            param(6) = nwxc_cam_alpha
723            param(7) = nwxc_cam_beta
724            param(8) = nwxc_cam_gamma
725            call nwxc_x_cams12(param,nwxc_rho_tol,ipol,nq,
726     +                         nwxc_wghts(it),rho,gamma,f)
727          case (NWXCP_X_CAMS12H)
728            param(1) = 1.02149642d0
729            param(2) = 0.757d0
730            param(3) = 0.00825905d0
731            param(4) = 0.00235804d0
732            param(5) = 0.00654977d0
733            param(6) = nwxc_cam_alpha
734            param(7) = nwxc_cam_beta
735            param(8) = nwxc_cam_gamma
736            call nwxc_x_cams12(param,nwxc_rho_tol,ipol,nq,
737     +                         nwxc_wghts(it),rho,gamma,f)
738          case (NWXCP_X_DLDF)
739            call nwxc_x_dldf(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
740     +                       rho,gamma,tau,f)
741          case (NWXCP_X_FT97)
742            call nwxc_x_ft97(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
743     +                       rho,gamma,f)
744          case (NWXCP_X_GILL)
745            call nwxc_x_gill(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
746     +                       rho,gamma,f)
747          case (NWXCP_X_HCTH)
748            param(1) = 4.0d0
749            param(2) = 0.109320d+01
750            param(3) =-0.744056d+00
751            param(4) = 0.559920d+01
752            param(5) =-0.678549d+01
753            param(6) = 0.449357d+01
754            call nwxc_x_b97(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
755     +                      rho,gamma,f)
756          case (NWXCP_X_HCTH120)
757            param(1) = 4.0d0
758            param(2) = 1.09163d0
759            param(3) =-0.74720d0
760            param(4) = 5.07830d0
761            param(5) =-4.10750d0
762            param(6) = 1.17170d0
763            call nwxc_x_b97(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
764     +                      rho,gamma,f)
765          case (NWXCP_X_HCTH147)
766            param(1) = 4.0d0
767            param(2) = 1.09025d0
768            param(3) =-0.79920d0
769            param(4) = 5.57210d0
770            param(5) =-5.86760d0
771            param(6) = 3.04540d0
772            call nwxc_x_b97(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
773     +                      rho,gamma,f)
774          case (NWXCP_X_HCTH407)
775            param(1) = 4.0d0
776            param(2) = 1.08184d0
777            param(3) =-0.5183d0
778            param(4) = 3.4256d0
779            param(5) =-2.6290d0
780            param(6) = 2.2886d0
781            call nwxc_x_b97(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
782     +                      rho,gamma,f)
783          case (NWXCP_X_HCTH407P)
784            param(1) = 4.0d0
785            param(2) = 1.08018D0
786            param(3) =-0.4117D0
787            param(4) = 2.4368D0
788            param(5) = 1.3890D0
789            param(6) =-1.3529D0
790            call nwxc_x_b97(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
791     +                      rho,gamma,f)
792          case (NWXCP_X_HCTH_A)
793            param(1) = 2.0d0
794            param(2) = 0.109878d+01
795            param(3) =-0.251173d+01
796            param(4) = 0.156233d-01
797            call nwxc_x_b97(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
798     +                      rho,gamma,f)
799          case (NWXCP_X_HCTHP14)
800            param(1) = 4.0d0
801            param(2) = 0.103161d+01
802            param(3) =-0.360781d+00
803            param(4) = 0.351994d+01
804            param(5) =-0.495944d+01
805            param(6) = 0.241165d+01
806            call nwxc_x_b97(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
807     +                      rho,gamma,f)
808          case (NWXCP_X_M05)
809            param( 1) =    0.08151d0
810            param( 2) =   -0.43956d0
811            param( 3) =   -3.22422d0
812            param( 4) =    2.01819d0
813            param( 5) =    8.79431d0
814            param( 6) =   -0.00295d0
815            param( 7) =    9.82029d0
816            param( 8) =   -4.82351d0
817            param( 9) =  -48.17574d0
818            param(10) =    3.64802d0
819            param(11) =   34.02248d0
820            call nwxc_x_m05(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
821     +                      rho,gamma,tau,f)
822          case (NWXCP_X_M05_2X)
823            param( 1) =   -0.56833d0
824            param( 2) =   -1.30057d0
825            param( 3) =    5.50070d0
826            param( 4) =    9.06402d0
827            param( 5) =  -32.21075d0
828            param( 6) =  -23.73298d0
829            param( 7) =   70.22996d0
830            param( 8) =   29.88614d0
831            param( 9) =  -60.25778d0
832            param(10) =  -13.22205d0
833            param(11) =   15.23694d0
834            call nwxc_x_m05(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
835     +                      rho,gamma,tau,f)
836          case (NWXCP_X_M06)
837            param( 1) =  1.422057D-01*Axlsda
838            param( 2) =  7.370319D-04*Axlsda
839            param( 3) = -1.601373D-02*Axlsda
840            param( 4) =  0.000000D+00
841            param( 5) =  0.000000D+00
842            param( 6) =  0.000000D+00
843            param( 7) =  5.877943D-01
844            param( 8) = -1.371776D-01
845            param( 9) =  2.682367D-01
846            param(10) = -2.515898D+00
847            param(11) = -2.978892D+00
848            param(12) =  8.710679D+00
849            param(13) =  1.688195D+01
850            param(14) = -4.489724D+00
851            param(15) = -3.299983D+01
852            param(16) = -1.449050D+01
853            param(17) =  2.043747D+01
854            param(18) =  1.256504D+01
855            call nwxc_x_m06(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
856     +                      rho,gamma,tau,f)
857          case (NWXCP_X_M06_HF)
858            param( 1) = -1.179732D-01*Axlsda
859            param( 2) = -2.500000D-03*Axlsda
860            param( 3) = -1.180065D-02*Axlsda
861            param( 4) =  0.000000D+00
862            param( 5) =  0.000000D+00
863            param( 6) =  0.000000D+00
864            param( 7) =  1.179732D-01
865            param( 8) = -1.066708D+00
866            param( 9) = -1.462405D-01
867            param(10) =  7.481848D+00
868            param(11) =  3.776679D+00
869            param(12) = -4.436118D+01
870            param(13) = -1.830962D+01
871            param(14) =  1.003903D+02
872            param(15) =  3.864360D+01
873            param(16) = -9.806018D+01
874            param(17) = -2.557716D+01
875            param(18) =  3.590404D+01
876            call nwxc_x_m06(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
877     +                      rho,gamma,tau,f)
878          case (NWXCP_X_M06_L)
879            param( 1) =  6.012244D-01*Axlsda
880            param( 2) =  4.748822D-03*Axlsda
881            param( 3) = -8.635108D-03*Axlsda
882            param( 4) = -9.308062D-06*Axlsda
883            param( 5) =  4.482811D-05*Axlsda
884            param( 6) =  0.000000D+00
885            param( 7) =  3.987756D-01
886            param( 8) =  2.548219D-01
887            param( 9) =  3.923994D-01
888            param(10) = -2.103655D+00
889            param(11) = -6.302147D+00
890            param(12) =  1.097615D+01
891            param(13) =  3.097273D+01
892            param(14) = -2.318489D+01
893            param(15) = -5.673480D+01
894            param(16) =  2.160364D+01
895            param(17) =  3.421814D+01
896            param(18) = -9.049762D+00
897            call nwxc_x_m06(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
898     +                      rho,gamma,tau,f)
899          case (NWXCP_X_M06_2X)
900            param( 1) =  4.600000D-01
901            param( 2) = -2.206052D-01
902            param( 3) = -9.431788D-02
903            param( 4) =  2.164494D+00
904            param( 5) = -2.556466D+00
905            param( 6) = -1.422133D+01
906            param( 7) =  1.555044D+01
907            param( 8) =  3.598078D+01
908            param( 9) = -2.722754D+01
909            param(10) = -3.924093D+01
910            param(11) =  1.522808D+01
911            param(12) =  1.522227D+01
912            call nwxc_x_m06_2x(param,nwxc_rho_tol,ipol,nq,
913     +           nwxc_wghts(it),rho,gamma,tau,f)
914          case (NWXCP_X_M08_HX)
915c           parameters A
916            param(01) =  1.3340172D+00
917            param(02) = -9.4751087D+00
918            param(03) = -1.2541893D+01
919            param(04) =  9.1369974D+00
920            param(05) =  3.4717204D+01
921            param(06) =  5.8831807D+01
922            param(07) =  7.1369574D+01
923            param(08) =  2.3312961D+01
924            param(09) =  4.8314679D+00
925            param(10) = -6.5044167D+00
926            param(11) = -1.4058265D+01
927            param(12) =  1.2880570D+01
928c           parameters B
929            param(13) = -8.5631823D-01
930            param(14) =  9.2810354D+00
931            param(15) =  1.2260749D+01
932            param(16) = -5.5189665D+00
933            param(17) = -3.5534989D+01
934            param(18) = -8.2049996D+01
935            param(19) = -6.8586558D+01
936            param(20) =  3.6085694D+01
937            param(21) = -9.3740983D+00
938            param(22) = -5.9731688D+01
939            param(23) =  1.6587868D+01
940            param(24) =  1.3993203D+01
941c           parameters C and D
942            do n = 25, 48
943              param(n) = 0.0d0
944            enddo
945            call nwxc_x_m08(param,nwxc_rho_tol,ipol,nq,
946     +           nwxc_wghts(it),rho,gamma,tau,f)
947          case (NWXCP_X_M08_SO)
948c           parameters A
949            param(01) = -3.4888428D-01
950            param(02) = -5.8157416D+00
951            param(03) =  3.7550810D+01
952            param(04) =  6.3727406D+01
953            param(05) = -5.3742313D+01
954            param(06) = -9.8595529D+01
955            param(07) =  1.6282216D+01
956            param(08) =  1.7513468D+01
957            param(09) = -6.7627553D+00
958            param(10) =  1.1106658D+01
959            param(11) =  1.5663545D+00
960            param(12) =  8.7603470D+00
961c           parameters B
962            param(13) =  7.8098428D-01
963            param(14) =  5.4538178D+00
964            param(15) = -3.7853348D+01
965            param(16) = -6.2295080D+01
966            param(17) =  4.6713254D+01
967            param(18) =  8.7321376D+01
968            param(19) =  1.6053446D+01
969            param(20) =  2.0126920D+01
970            param(21) = -4.0343695D+01
971            param(22) = -5.8577565D+01
972            param(23) =  2.0890272D+01
973            param(24) =  1.0946903D+01
974c           parameters C and D
975            do n = 25, 48
976              param(n) = 0.0d0
977            enddo
978            call nwxc_x_m08(param,nwxc_rho_tol,ipol,nq,
979     +           nwxc_wghts(it),rho,gamma,tau,f)
980          case (NWXCP_X_M11)
981c           parameters A
982            param(01) = -0.18399900D+00
983            param(02) = -1.39046703D+01
984            param(03) =  1.18206837D+01
985            param(04) =  3.10098465D+01
986            param(05) = -5.19625696D+01
987            param(06) =  1.55750312D+01
988            param(07) = -6.94775730D+00
989            param(08) = -1.58465014D+02
990            param(09) = -1.48447565D+00
991            param(10) =  5.51042124D+01
992            param(11) = -1.34714184D+01
993            param(12) =  0.00000000D+00
994c           parameters B
995            param(13) =  0.75599900D+00
996            param(14) =  1.37137944D+01
997            param(15) = -1.27998304D+01
998            param(16) = -2.93428814D+01
999            param(17) =  5.91075674D+01
1000            param(18) = -2.27604866D+01
1001            param(19) = -1.02769340D+01
1002            param(20) =  1.64752731D+02
1003            param(21) =  1.85349258D+01
1004            param(22) = -5.56825639D+01
1005            param(23) =  7.47980859D+00
1006            param(24) =  0.00000000D+00
1007c           parameters C and D
1008            do n = 25, 48
1009              param(n) = 0.0d0
1010            enddo
1011            call nwxc_x_m11(param,nwxc_rho_tol,ipol,nq,
1012     +           nwxc_wghts(it),rho,gamma,tau,f)
1013          case (NWXCP_X_M11_L)
1014c           parameters A
1015            param(01) =  8.121131D-01
1016            param(02) =  1.738124D+01
1017            param(03) =  1.154007D+00
1018            param(04) =  6.869556D+01
1019            param(05) =  1.016864D+02
1020            param(06) = -5.887467D+00
1021            param(07) =  4.517409D+01
1022            param(08) = -2.773149D+00
1023            param(09) = -2.617211D+01
1024            param(10) =  0.000000D+00
1025            param(11) =  0.000000D+00
1026            param(12) =  0.000000D+00
1027c           parameters B
1028            param(13) =  1.878869D-01
1029            param(14) = -1.653877D+01
1030            param(15) =  6.755753D-01
1031            param(16) = -7.567572D+01
1032            param(17) = -1.040272D+02
1033            param(18) =  1.831853D+01
1034            param(19) = -5.573352D+01
1035            param(20) = -3.520210D+00
1036            param(21) =  3.724276D+01
1037            param(22) =  0.000000D+00
1038            param(23) =  0.000000D+00
1039            param(24) =  0.000000D+00
1040c           parameters C
1041            param(25) = -4.386615D-01
1042            param(26) = -1.214016D+02
1043            param(27) = -1.393573D+02
1044            param(28) = -2.046649D+00
1045            param(29) =  2.804098D+01
1046            param(30) = -1.312258D+01
1047            param(31) = -6.361819D+00
1048            param(32) = -8.055758D-01
1049            param(33) =  3.736551D+00
1050            param(34) =  0.000000D+00
1051            param(35) =  0.000000D+00
1052            param(36) =  0.000000D+00
1053c           parameters D
1054            param(37) =  1.438662D+00
1055            param(38) =  1.209465D+02
1056            param(39) =  1.328252D+02
1057            param(40) =  1.296355D+01
1058            param(41) =  5.854866D+00
1059            param(42) = -3.378162D+00
1060            param(43) = -4.423393D+01
1061            param(44) =  6.844475D+00
1062            param(45) =  1.949541D+01
1063            param(46) =  0.000000D+00
1064            param(47) =  0.000000D+00
1065            param(48) =  0.000000D+00
1066            call nwxc_x_m11(param,nwxc_rho_tol,ipol,nq,
1067     +           nwxc_wghts(it),rho,gamma,tau,f)
1068          case (NWXCP_X_MPW91)
1069            param(1) = 3.72d0
1070            param(2) = 0.00426D0
1071            call nwxc_x_pw91(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1072     +                       rho,gamma,f)
1073          case (NWXCP_X_OPT)
1074            call nwxc_x_opt(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1075     +                      rho,gamma,f)
1076          case (NWXCP_X_PW6B95)
1077            param(1) = 0.00538d0
1078            param(2) = 1.7382d0
1079            param(3) = 3.8901d0
1080            call nwxc_x_pw6(param,nwxc_rho_tol,ipol,nq,
1081     +                      nwxc_wghts(it),rho,gamma,f)
1082          case (NWXCP_X_PWB6K)
1083            param(1) = 0.00539d0
1084            param(2) = 1.7077d0
1085            param(3) = 4.0876d0
1086            call nwxc_x_pw6(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1087     +                      rho,gamma,f)
1088          case (NWXCP_X_PW91)
1089            param(1) = 4.0d0
1090            param(2) = 0.0042D0
1091            call nwxc_x_pw91(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1092     +                       rho,gamma,f)
1093          case (NWXCP_X_PBE)
1094            param(1) = 0.8040d0
1095            param(2) = 0.2195149727645171d0
1096            call nwxc_x_pbe(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1097     +                      rho,gamma,f)
1098          case (NWXCP_X_PBESOL)
1099            param(1) = 0.8040d0
1100            param(2) = 10.0d0/81.0d0
1101            call nwxc_x_pbe(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1102     +                      rho,gamma,f)
1103          case (NWXCP_X_REVPBE)
1104            param(1) = 1.245d0
1105            param(2) = 0.2195149727645171d0
1106            call nwxc_x_pbe(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1107     +                      rho,gamma,f)
1108          case (NWXCP_X_RPBE)
1109            call nwxc_x_rpbe(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1110     +                       rho,gamma,f)
1111          case (NWXCP_X_PKZB)
1112            call nwxc_x_pkzb99(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1113     +                         rho,gamma,tau,f)
1114          case (NWXCP_X_S12G)
1115            param(1) = 1.03842032d0
1116            param(2) = 0.757d0
1117            param(3) = 0.00403198d0
1118            param(4) = 0.00104596d0
1119            param(5) = 0.00594635d0
1120            call nwxc_x_s12(param,nwxc_rho_tol,ipol,nq,
1121     +                      nwxc_wghts(it),rho,gamma,f)
1122          case (NWXCP_X_S12H)
1123            param(1) = 1.02543951d0
1124            param(2) = 0.757d0
1125            param(3) = 0.00761554d0
1126            param(4) = 0.00211063d0
1127            param(5) = 0.00604672d0
1128            call nwxc_x_s12(param,nwxc_rho_tol,ipol,nq,
1129     +                      nwxc_wghts(it),rho,gamma,f)
1130          case (NWXCP_X_SOGGA)
1131            param(1)  =  0.5d0
1132            param(2)  =  0.276d0
1133            param(3)  =  0.0d0
1134            param(4)  =  0.0d0
1135            param(5)  =  0.0d0
1136            param(6)  =  0.0d0
1137            param(7)  =  0.5d0
1138            param(8)  =  0.276d0
1139            param(9)  =  0.0d0
1140            param(10) =  0.0d0
1141            param(11) =  0.0d0
1142            param(12) =  0.0d0
1143            call nwxc_x_sogga(param,nwxc_rho_tol,ipol,nq,
1144     +                        nwxc_wghts(it),rho,gamma,f)
1145          case (NWXCP_X_SOGGA11)
1146            param(1)  =  0.5d0
1147            param(2)  = -2.95535d0
1148            param(3)  =  15.7974d0
1149            param(4)  = -91.1804d0
1150            param(5)  =  96.2030d0
1151            param(6)  =  0.18683d0
1152            param(7)  =  0.50000d0
1153            param(8)  =  3.50743d0
1154            param(9)  = -12.9523d0
1155            param(10) =  49.7870d0
1156            param(11) = -33.2545d0
1157            param(12) = -11.1396d0
1158            call nwxc_x_sogga(param,nwxc_rho_tol,ipol,nq,
1159     +                        nwxc_wghts(it),rho,gamma,f)
1160          case (NWXCP_X_SOGGA11_X)
1161            param(1)  =  2.99250d-01
1162            param(2)  =  3.21638d+00
1163            param(3)  = -3.55605d+00
1164            param(4)  =  7.65852d+00
1165            param(5)  = -1.12830d+01
1166            param(6)  =  5.25813d+00
1167            param(7)  =  2.99250d-01
1168            param(8)  = -2.88595d+00
1169            param(9)  =  3.23617d+00
1170            param(10) = -2.45393d+00
1171            param(11) = -3.75495d+00
1172            param(12) =  3.96613d+00
1173            call nwxc_x_sogga(param,nwxc_rho_tol,ipol,nq,
1174     +                        nwxc_wghts(it),rho,gamma,f)
1175          case (NWXCP_X_SSB_D)
1176            call nwxc_x_ssbD_1(nwxc_rho_tol,ipol,nq,
1177     +                         nwxc_wghts(it),rho,gamma,f)
1178          case (NWXCP_X_TPSS)
1179            call nwxc_x_tpss03(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1180     +                         rho,gamma,tau,f)
1181          case (NWXCP_X_WPBE)
1182            param(1) = nwxc_cam_gamma
1183            call nwxc_x_wpbe(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1184     +                       rho,gamma,f)
1185          case (NWXCP_X_VS98)
1186            param(1) =  -9.800683d-01
1187            param(2) =  -3.556788d-03
1188            param(3) =   6.250326d-03
1189            param(4) =  -2.354518d-05
1190            param(5) =  -1.282732d-04
1191            param(6) =   3.574822d-04
1192            call nwxc_x_vs98(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1193     +                       rho,gamma,tau,f)
1194          case (NWXCP_C_B95)
1195            param(1) = 0.0031d0
1196            param(2) = 0.038d0
1197            call nwxc_c_b95(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1198     +                      rho,gamma,tau,f)
1199          case (NWXCP_C_B97)
1200            param(1) = 2.0d0
1201            param(2) = 0.17370d+00
1202            param(3) = 0.94540d+00
1203            param(4) = 0.23487d+01
1204            param(5) = 0.74710d+00
1205            param(6) =-0.24868d+01
1206            param(7) =-0.45961d+01
1207            call nwxc_c_b97(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1208     +                      rho,gamma,f)
1209          case (NWXCP_C_B97_1)
1210            param(1) = 2.0d0
1211            param(2) = 0.820011d-01
1212            param(3) = 0.955689d+00
1213            param(4) = 0.271681d+01
1214            param(5) = 0.788552d+00
1215            param(6) =-0.287103d+01
1216            param(7) =-0.547869d+01
1217            call nwxc_c_b97(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1218     +                      rho,gamma,f)
1219          case (NWXCP_C_B97_2)
1220            param(1) = 2.0d0
1221            param(2) = 0.585808D+00
1222            param(3) = 0.999849D+00
1223            param(4) =-0.691682D+00
1224            param(5) = 0.140626D+01
1225            param(6) = 0.394796D+00
1226            param(7) =-0.744060D+01
1227            call nwxc_c_b97(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1228     +                      rho,gamma,f)
1229          case (NWXCP_C_B97_3)
1230            param(1)  = 4.0d0
1231            param(2)  = 5.623649D-01
1232            param(3)  = 1.133830D+00
1233            param(4)  =-1.322980D+00
1234            param(5)  =-2.811967D+00
1235            param(6)  = 6.359191D+00
1236            param(7)  = 7.431302D+00
1237            param(8)  =-7.464002D+00
1238            param(9)  =-1.969342D+00
1239            param(10) = 1.827082D+00
1240            param(11) =-1.174423D+01
1241            call nwxc_c_b97(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1242     +                      rho,gamma,f)
1243          case (NWXCP_C_B97_D)
1244            param(1) = 2.0d0
1245            param(2) = 0.22340d+00
1246            param(3) = 0.690410d+00
1247            param(4) =-1.562080d+00
1248            param(5) = 6.302700d00
1249            param(6) = 1.942930d+0
1250            param(7) =-14.97120d+00
1251            call nwxc_c_b97(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1252     +                      rho,gamma,f)
1253          case (NWXCP_C_B97_G)
1254            param(1) = 2.0d0
1255            param(2) = 0.4883d0
1256            param(3) = 0.7961d0
1257            param(4) =-2.117d0
1258            param(5) = 5.7060d0
1259            param(6) = 2.3235d0
1260            param(7) =-14.9820d0
1261            call nwxc_c_b97(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1262     +                      rho,gamma,f)
1263          case (NWXCP_C_B98)
1264            param(1) = 2.0d0
1265            param(2) =-0.120163d00
1266            param(3) = 0.934715d00
1267            param(4) = 2.82332d0
1268            param(5) = 1.14105d0
1269            param(6) =-2.59412d0
1270            param(7) =-5.33398d0
1271            call nwxc_c_b97(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1272     +                      rho,gamma,f)
1273          case (NWXCP_C_DLDF)
1274            call nwxc_c_dldf(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1275     +                       rho,gamma,tau,f)
1276          case (NWXCP_C_FT97)
1277            call nwxc_c_ft97(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1278     +                       rho,gamma,f)
1279          case (NWXCP_C_HCTH)
1280            param(1)  = 4.0d0
1281            param(2)  = 0.222601d0
1282            param(3)  = 0.729974d0
1283            param(4)  =-3.38622d-002
1284            param(5)  = 3.352870d0
1285            param(6)  =-1.25170d-002
1286            param(7)  =-11.543d0
1287            param(8)  =-0.802496d0
1288            param(9)  = 8.085640d0
1289            param(10) = 1.553960d0
1290            param(11) =-4.478570d0
1291            call nwxc_c_b97(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1292     +                      rho,gamma,f)
1293          case (NWXCP_C_HCTH120)
1294            param(1)  = 4.0d0
1295            param(2)  = 0.48951d0
1296            param(3)  = 0.51473d0
1297            param(4)  =-0.26070d0
1298            param(5)  = 6.92980d0
1299            param(6)  = 0.43290d0
1300            param(7)  =-24.7070d0
1301            param(8)  =-1.99250d0
1302            param(9)  = 23.1100d0
1303            param(10) = 2.48530d0
1304            param(11) =-11.3230d0
1305            call nwxc_c_b97(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1306     +                      rho,gamma,f)
1307          case (NWXCP_C_HCTH147)
1308            param(1)  = 4.0d0
1309            param(2)  = 0.56258d0
1310            param(3)  = 0.54235d0
1311            param(4)  =-1.71000d-002
1312            param(5)  = 7.01460d0
1313            param(6)  =-1.30640d0
1314            param(7)  =-28.3820d0
1315            param(8)  = 1.05750d0
1316            param(9)  = 35.0330d0
1317            param(10) = 0.88540d0
1318            param(11) =-20.4280d0
1319            call nwxc_c_b97(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1320     +                      rho,gamma,f)
1321          case (NWXCP_C_HCTH407)
1322            param(1)  = 4.0d0
1323            param(2)  = 1.18777d0
1324            param(3)  = 0.58908d0
1325            param(4)  =-2.40290d0
1326            param(5)  = 4.42370d0
1327            param(6)  = 5.61740d0
1328            param(7)  =-19.2220d0
1329            param(8)  =-9.17920d0
1330            param(9)  = 42.5720d0
1331            param(10) = 6.24800d0
1332            param(11) =-42.0050d0
1333            call nwxc_c_b97(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1334     +                      rho,gamma,f)
1335          case (NWXCP_C_HCTH407P)
1336            param(1)  = 4.0d0
1337            param(2)  = 0.80302d0
1338            param(3)  = 0.73604d0
1339            param(4)  =-1.04790d0
1340            param(5)  = 3.02700d0
1341            param(6)  = 4.98070d0
1342            param(7)  =-10.0750d0
1343            param(8)  =-12.8900d0
1344            param(9)  = 20.6110d0
1345            param(10) = 9.64460d0
1346            param(11) =-29.4180d0
1347            call nwxc_c_b97(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1348     +                      rho,gamma,f)
1349          case (NWXCP_C_HCTH_A)
1350            param(1)  = 4.0d0
1351            param(2)  = 1.36823d-002
1352            param(3)  = 0.836897d0
1353            param(4)  = 0.268920d0
1354            param(5)  = 1.720510d0
1355            param(6)  =-0.550769d0
1356            param(7)  =-2.784980d0
1357            param(8)  = 1.039470d0
1358            param(9)  =-4.575040d0
1359            param(10) = 0.000000d0
1360            param(11) = 0.000000d0
1361            call nwxc_c_b97(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1362     +                      rho,gamma,f)
1363          case (NWXCP_C_HCTHP14)
1364            param(1)  = 4.0d0
1365            param(2)  = 2.82414d0
1366            param(3)  = 8.21827d-002
1367            param(4)  = 3.18843d-002
1368            param(5)  = 4.56466d0
1369            param(6)  =-1.78512d0
1370            param(7)  =-13.5529d0
1371            param(8)  = 2.39795d0
1372            param(9)  = 13.3820d0
1373            param(10) =-0.876909d0
1374            param(11) =-3.174930d0
1375            call nwxc_c_b97(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1376     +                      rho,gamma,f)
1377          case (NWXCP_C_M05)
1378            param( 1) =   1.00000d0
1379            param( 2) =   3.78569d0
1380            param( 3) = -14.15261d0
1381            param( 4) =  -7.46589d0
1382            param( 5) =  17.94491d0
1383            param( 6) =   1.00000d0
1384            param( 7) =   3.77344d0
1385            param( 8) = -26.04463d0
1386            param( 9) =  30.69913d0
1387            param(10) =  -9.22695d0
1388            call nwxc_c_m05(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1389     +                      rho,gamma,tau,f)
1390          case (NWXCP_C_M05_2X)
1391            param( 1) =   1.00000d0
1392            param( 2) =   1.09297d0
1393            param( 3) =  -3.79171d0
1394            param( 4) =   2.82810d0
1395            param( 5) = -10.58909d0
1396            param( 6) =   1.00000d0
1397            param( 7) =  -3.05430d0
1398            param( 8) =   7.61854d0
1399            param( 9) =   1.47665d0
1400            param(10) = -11.92365d0
1401            call nwxc_c_m05(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1402     +                      rho,gamma,tau,f)
1403          case (NWXCP_C_M06)
1404c
1405            param( 1) =  -2.741539D+00
1406            param( 2) =  -6.720113D-01
1407            param( 3) =  -7.932688D-02
1408            param( 4) =   1.918681D-03
1409            param( 5) =  -2.032902D-03
1410            param( 6) =   0.000000D+00
1411            param( 7) =   4.905945D-01
1412            param( 8) =  -1.437348D-01
1413            param( 9) =   2.357824D-01
1414            param(10) =   1.871015D-03
1415            param(11) =  -3.788963D-03
1416            param(12) =   0.000000D+00
1417c
1418            param(13) =   3.741539D+00
1419            param(14) =   2.187098D+02
1420            param(15) =  -4.531252D+02
1421            param(16) =   2.936479D+02
1422            param(17) =  -6.287470D+01
1423            param(18) =   5.094055D-01
1424            param(19) =  -1.491085D+00
1425            param(20) =   1.723922D+01
1426            param(21) =  -3.859018D+01
1427            param(22) =   2.845044D+01
1428c
1429            call nwxc_c_m06(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1430     +                      rho,gamma,tau,f)
1431          case (NWXCP_C_M06_HF)
1432c
1433            param( 1) =  -6.746338D-01
1434            param( 2) =  -1.534002D-01
1435            param( 3) =  -9.021521D-02
1436            param( 4) =  -1.292037D-03
1437            param( 5) =  -2.352983D-04
1438            param( 6) =   0.000000D+00
1439            param( 7) =   8.976746D-01
1440            param( 8) =  -2.345830D-01
1441            param( 9) =   2.368173D-01
1442            param(10) =  -9.913890D-04
1443            param(11) =  -1.146165D-02
1444            param(12) =   0.000000D+00
1445c
1446            param(13) =   1.674634D+00
1447            param(14) =   5.732017D+01
1448            param(15) =   5.955416D+01
1449            param(16) =  -2.311007D+02
1450            param(17) =   1.255199D+02
1451            param(18) =   1.023254D-01
1452            param(19) =  -2.453783D+00
1453            param(20) =   2.913180D+01
1454            param(21) =  -3.494358D+01
1455            param(22) =   2.315955D+01
1456c
1457            call nwxc_c_m06(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1458     +                      rho,gamma,tau,f)
1459          case (NWXCP_C_M06_L)
1460c
1461            param( 1) =   3.957626D-01
1462            param( 2) =  -5.614546D-01
1463            param( 3) =   1.403963D-02
1464            param( 4) =   9.831442D-04
1465            param( 5) =  -3.577176D-03
1466            param( 6) =   0.000000D+00
1467            param( 7) =   4.650534D-01
1468            param( 8) =   1.617589D-01
1469            param( 9) =   1.833657D-01
1470            param(10) =   4.692100D-04
1471            param(11) =  -4.990573D-03
1472            param(12) =   0.000000D+00
1473c
1474            param(13) =   6.042374D-01
1475            param(14) =   1.776783D+02
1476            param(15) =  -2.513252D+02
1477            param(16) =   7.635173D+01
1478            param(17) =  -1.255699D+01
1479            param(18) =   5.349466D-01
1480            param(19) =   5.396620D-01
1481            param(20) =  -3.161217D+01
1482            param(21) =   5.149592D+01
1483            param(22) =  -2.919613D+01
1484c
1485            call nwxc_c_m06(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1486     +                      rho,gamma,tau,f)
1487          case (NWXCP_C_M06_2X)
1488c
1489            param( 1) =   1.166404D-01
1490            param( 2) =  -9.120847D-02
1491            param( 3) =  -6.726189D-02
1492            param( 4) =   6.720580D-05
1493            param( 5) =   8.448011D-04
1494            param( 6) =   0.000000D+00
1495            param( 7) =   6.902145D-01
1496            param( 8) =   9.847204D-02
1497            param( 9) =   2.214797D-01
1498            param(10) =  -1.968264D-03
1499            param(11) =  -6.775479D-03
1500            param(12) =   0.000000D+00
1501c
1502            param(13) =   8.833596D-01
1503            param(14) =   3.357972D+01
1504            param(15) =  -7.043548D+01
1505            param(16) =   4.978271D+01
1506            param(17) =  -1.852891D+01
1507            param(18) =   3.097855D-01
1508            param(19) =  -5.528642D+00
1509            param(20) =   1.347420D+01
1510            param(21) =  -3.213623D+01
1511            param(22) =   2.846742D+01
1512c
1513            call nwxc_c_m06(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1514     +                      rho,gamma,tau,f)
1515          case (NWXCP_C_M08_HX)
1516c           parameters A
1517            param(1)  =    1.0000000D+00
1518            param(2)  =   -4.0661387D-01
1519            param(3)  =   -3.3232530D+00
1520            param(4)  =    1.5540980D+00
1521            param(5)  =    4.4248033D+01
1522            param(6)  =   -8.4351930D+01
1523            param(7)  =   -1.1955581D+02
1524            param(8)  =    3.9147081D+02
1525            param(9)  =    1.8363851D+02
1526            param(10) =   -6.3268223D+02
1527            param(11) =   -1.1297403D+02
1528            param(12) =    3.3629312D+02
1529c           parameters B
1530            param(13) =    1.3812334D+00
1531            param(14) =   -2.4683806D+00
1532            param(15) =   -1.1901501D+01
1533            param(16) =   -5.4112667D+01
1534            param(17) =    1.0055846D+01
1535            param(18) =    1.4800687D+02
1536            param(19) =    1.1561420D+02
1537            param(20) =    2.5591815D+02
1538            param(21) =    2.1320772D+02
1539            param(22) =   -4.8412067D+02
1540            param(23) =   -4.3430813D+02
1541            param(24) =    5.6627964D+01
1542            call nwxc_c_m11(param,nwxc_rho_tol,ipol,nq,
1543     +           nwxc_wghts(it),rho,gamma,tau,f)
1544          case (NWXCP_C_M08_SO)
1545c           parameters A
1546            param(1)  =   1.0000000D+00
1547            param(2)  =   0.0000000D+00
1548            param(3)  =  -3.9980886D+00
1549            param(4)  =   1.2982340D+01
1550            param(5)  =   1.0117507D+02
1551            param(6)  =  -8.9541984D+01
1552            param(7)  =  -3.5640242D+02
1553            param(8)  =   2.0698803D+02
1554            param(9)  =   4.6037780D+02
1555            param(10) =  -2.4510559D+02
1556            param(11) = -1.9638425D+02
1557            param(12) =  1.1881459D+02
1558c           parameters B
1559            param(13) =   1.0000000D+00
1560            param(14) =  -4.4117403D+00
1561            param(15) =  -6.4128622D+00
1562            param(16) =   4.7583635D+01
1563            param(17) =   1.8630053D+02
1564            param(18) =  -1.2800784D+02
1565            param(19) =  -5.5385258D+02
1566            param(20) =   1.3873727D+02
1567            param(21) =   4.1646537D+02
1568            param(22) =  -2.6626577D+02
1569            param(23) =   5.6676300D+01
1570            param(24) =   3.1673746D+02
1571            call nwxc_c_m11(param,nwxc_rho_tol,ipol,nq,
1572     +           nwxc_wghts(it),rho,gamma,tau,f)
1573          case (NWXCP_C_M11)
1574c           parameters A
1575            param(1)  =  1.0000000D+00
1576            param(2)  =  0.0000000D+00
1577            param(3)  = -3.8933250D+00
1578            param(4)  = -2.1688455D+00
1579            param(5)  =  9.3497200D+00
1580            param(6)  = -1.9845140D+01
1581            param(7)  =  2.3455253D+00
1582            param(8)  =  7.9246513D+01
1583            param(9)  =  9.6042757D+00
1584            param(10) = -6.7856719D+01
1585            param(11) = -9.1841067D+00
1586            param(12) =  0.0000000D+00
1587c           parameters B
1588            param(13) =  7.2239798D-01
1589            param(14) =  4.3730564D-01
1590            param(15) = -1.6088809D+01
1591            param(16) = -6.5542437D+01
1592            param(17) =  3.2057230D+01
1593            param(18) =  1.8617888D+02
1594            param(19) =  2.0483468D+01
1595            param(20) = -7.0853739D+01
1596            param(21) =  4.4483915D+01
1597            param(22) = -9.4484747D+01
1598            param(23) = -1.1459868D+02
1599            param(24) =  0.0000000D+00
1600            call nwxc_c_m11(param,nwxc_rho_tol,ipol,nq,
1601     +           nwxc_wghts(it),rho,gamma,tau,f)
1602          case (NWXCP_C_M11_L)
1603c           parameters A
1604            param(1)  =  1.000000D+00
1605            param(2)  =  0.000000D+00
1606            param(3)  =  2.750880D+00
1607            param(4)  = -1.562287D+01
1608            param(5)  =  9.363381D+00
1609            param(6)  =  2.141024D+01
1610            param(7)  = -1.424975D+01
1611            param(8)  = -1.134712D+01
1612            param(9)  =  1.022365D+01
1613            param(10) =  0.000000D+00
1614            param(11) =  0.000000D+00
1615            param(12) =  0.000000D+00
1616c           parameters B
1617            param(13) =  1.000000D+00
1618            param(14) = -9.082060D+00
1619            param(15) =  6.134682D+00
1620            param(16) = -1.333216D+01
1621            param(17) = -1.464115D+01
1622            param(18) =  1.713143D+01
1623            param(19) =  2.480738D+00
1624            param(20) = -1.007036D+01
1625            param(21) = -1.117521D-01
1626            param(22) =  0.000000D+00
1627            param(23) =  0.000000D+00
1628            param(24) =  0.000000D+00
1629            call nwxc_c_m11(param,nwxc_rho_tol,ipol,nq,
1630     +           nwxc_wghts(it),rho,gamma,tau,f)
1631          case (NWXCP_C_MPBE)
1632            param(1) = 0.066724550603149d0
1633            call nwxc_c_mpbe(param,nwxc_rho_tol,ipol,nq,
1634     +           nwxc_wghts(it),rho,gamma,f)
1635          case (NWXCP_C_OP)
1636            param(1) = 2.3670d0
1637            call nwxc_c_op(nwxc_k_becke88,param,nwxc_rho_tol,ipol,nq,
1638     +           nwxc_wghts(it),rho,gamma,f)
1639          case (NWXCP_C_OPT)
1640            call nwxc_c_opt(nwxc_rho_tol,ipol,nq,
1641     +           nwxc_wghts(it),rho,gamma,f)
1642          case (NWXCP_C_PW6B95)
1643            param(1) = 0.00262d0
1644            param(2) = 0.03668d0
1645            call nwxc_c_b95(param,nwxc_rho_tol,ipol,nq,
1646     +                      nwxc_wghts(it),rho,gamma,tau,f)
1647          case (NWXCP_C_PWB6K)
1648            param(1) = 0.00353d0
1649            param(2) = 0.04120d0
1650            call nwxc_c_b95(param,nwxc_rho_tol,ipol,nq,
1651     +                      nwxc_wghts(it),rho,gamma,tau,f)
1652          case (NWXCP_C_PW91LDA)
1653            call nwxc_c_pw91lda(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1654     +                          rho,f)
1655          case (NWXCP_C_LYP)
1656            call nwxc_c_lyp(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1657     +                      rho,gamma,f)
1658          case (NWXCP_C_PZ81)
1659            call nwxc_c_perdew81(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1660     +                           rho,f)
1661          case (NWXCP_C_P86)
1662            call nwxc_c_perdew86(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1663     +                           rho,gamma,f)
1664          case (NWXCP_C_P91)
1665            call nwxc_c_p91(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1666     +                      rho,gamma,f)
1667          case (NWXCP_C_P91_VWN5)
1668            call nwxc_c_p91_vwn5(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1669     +                           rho,gamma,f)
1670          case (NWXCP_C_PBE)
1671            param(1) = 0.066724550603149d0
1672            call nwxc_c_pbe(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1673     +                      rho,gamma,f)
1674          case (NWXCP_C_PBESOL)
1675            param(1) = 0.046d0
1676            call nwxc_c_pbe(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1677     +                      rho,gamma,f)
1678          case (NWXCP_C_PKZB)
1679            param(1) = 0.066724550603149d0
1680            call nwxc_c_pkzb99(param,nwxc_rho_tol,ipol,nq,
1681     +                         nwxc_wghts(it),rho,gamma,tau,f)
1682          case (NWXCP_C_SPBE)
1683            call nwxc_c_spbe(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1684     +                       rho,gamma,f)
1685          case (NWXCP_C_SOGGA11)
1686            param(1)  =  5.00000d-01
1687            param(2)  = -4.62334D+00
1688            param(3)  =  8.00410D+00
1689            param(4)  = -130.226D+00
1690            param(5)  =  38.2685D+00
1691            param(6)  =  69.5599D+00
1692            param(7)  =  5.00000d-01
1693            param(8)  =  3.62334D+00
1694            param(9)  =  9.36393D+00
1695            param(10) =  34.5114D+00
1696            param(11) = -18.5684D+00
1697            param(12) = -0.16519D+00
1698            call nwxc_c_sogga(param,nwxc_rho_tol,ipol,nq,
1699     +                        nwxc_wghts(it),rho,gamma,f)
1700          case (NWXCP_C_SOGGA11_X)
1701            param(1)  =  5.00000d-01
1702            param(2)  =  7.82439d+01
1703            param(3)  =  2.57211d+01
1704            param(4)  = -1.38830d+01
1705            param(5)  = -9.87375d+00
1706            param(6)  = -1.41357d+01
1707            param(7)  =  5.00000d-01
1708            param(8)  = -7.92439d+01
1709            param(9)  =  1.63725d+01
1710            param(10) =  2.08129d+00
1711            param(11) =  7.50769d+00
1712            param(12) = -1.01861d+01
1713            call nwxc_c_sogga(param,nwxc_rho_tol,ipol,nq,
1714     +                        nwxc_wghts(it),rho,gamma,f)
1715          case (NWXCP_C_TPSS)
1716            param(1) = 0.066724550603149d0
1717            call nwxc_c_tpss03(param,nwxc_rho_tol,ipol,nq,
1718     +                         nwxc_wghts(it),rho,gamma,tau,f)
1719          case (NWXCP_C_VS98)
1720            param(1)  =  7.035010d-01
1721            param(2)  =  7.694574d-03
1722            param(3)  =  5.152765d-02
1723            param(4)  =  3.394308d-05
1724            param(5)  = -1.269420d-03
1725            param(6)  =  1.296118d-03
1726            param(7)  =  3.270912d-01
1727            param(8)  = -3.228915d-02
1728            param(9)  = -2.942406d-02
1729            param(10) =  2.134222d-03
1730            param(11) = -5.451559d-03
1731            param(12) =  1.577575d-02
1732            call nwxc_c_vs98(param,nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1733     +                       rho,gamma,tau,f)
1734          case (NWXCP_C_VWN1)
1735            call nwxc_c_vwn1(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1736     +                       rho,f)
1737          case (NWXCP_C_VWN1_RPA)
1738            call nwxc_c_vwn1_rpa(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1739     +                           rho,f)
1740          case (NWXCP_C_VWN2)
1741            call nwxc_c_vwn2(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1742     +                       rho,f)
1743          case (NWXCP_C_VWN3)
1744            call nwxc_c_vwn3(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1745     +                       rho,f)
1746          case (NWXCP_C_VWN4)
1747            call nwxc_c_vwn4(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1748     +                       rho,f)
1749          case (NWXCP_C_VWN5)
1750            call nwxc_c_vwn5(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1751     +                       rho,f)
1752          case (NWXCP_BOP)
1753            param(1) = 2.3670d0
1754            call nwxc_c_op(nwxc_k_becke88,param,nwxc_rho_tol,ipol,nq,
1755     +           nwxc_wghts(it),rho,gamma,f)
1756          case (NWXCP_KT1)
1757            call nwxc_xc_kt1(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
1758     +                       rho,gamma,f)
1759          case (NWXCP_PBEOP)
1760            param(1) = 2.3789d0
1761            call nwxc_c_op(nwxc_k_pbe96,param,nwxc_rho_tol,ipol,nq,
1762     +           nwxc_wghts(it),rho,gamma,f)
1763          case (NWXCP_SOP)
1764            param(1) = 2.5654d0
1765            call nwxc_c_op(nwxc_k_dirac,param,nwxc_rho_tol,ipol,nq,
1766     +           nwxc_wghts(it),rho,gamma,f)
1767          case default
1768            if (nwxc_oroot) then
1769              write(*,*)"nwxc_eval_df: invalid functional",nwxc_ids(it)
1770            endif
1771            call nwxc_printP()
1772            call errquit("nwxc_eval_df: invalid functional",
1773     +                    nwxc_ids(it),0)
1774        end select
1775      enddo
1776C
1777      end
1778C>
1779C> @}
1780C>
1781C> \ingroup nwad_api
1782C> @{
1783C>
1784C> \brief The functional, 1st and 2nd order partial derivative
1785C> evaluation
1786C>
1787      subroutine nwxc_eval_df2(ipol,nq,rho,gamma,tau,f,dfdr,dfdr2,
1788     +                         dfdg,dfdg2,dfdt,dfdt2)
1789      implicit none
1790#include "errquit.fh"
1791#include "nwxcP.fh"
1792#include "nwxc_param.fh"
1793      integer ipol !< [Input] The number of spin channels
1794      integer nq   !< [Input] The number of points
1795C
1796      double precision rho(nq,ipol)     !< [Input] Density
1797      double precision gamma(nq,ipol+1) !< [Input] |Density gradient|^2
1798      double precision tau(nq,ipol)     !< [Input] Kinetic energy
1799                                        !< density
1800C
1801      double precision f(nq)           !< [Output] Energy
1802      double precision dfdr(nq,ipol)   !< [Output] Derivative wrt rho
1803      double precision dfdg(nq,ipol+1) !< [Output] Derivative wrt gamma
1804      double precision dfdt(nq,ipol)   !< [Output] Derivative wrt tau
1805      double precision dfdr2(nq,NCOL_AMAT2) !< [Output] 2nd derivative wrt rho
1806      double precision dfdg2(nq,NCOL_CMAT2) !< [Output] 2nd derivative wrt gamma
1807      double precision dfdt2(nq,NCOL_MMAT2) !< [Output] 2nd derivative wrt tau
1808C
1809      if (nwxc_eval_method.eq.NWXCP_EVAL_AUTODF) then
1810        call nwxca_eval_df2(ipol,nq,rho,gamma,tau,f,dfdr,dfdr2,
1811     +                      dfdg,dfdg2,dfdt,dfdt2)
1812      else if (nwxc_eval_method.eq.NWXCP_EVAL_MAXIMA) then
1813        call nwxcm_eval_df2(ipol,nq,rho,gamma,tau,f,dfdr,dfdr2,
1814     +                      dfdg,dfdg2,dfdt,dfdt2)
1815      else
1816        call errquit("nwxc_eval_df: unknown evaluator",nwxc_eval_method,
1817     +               UERR)
1818      endif
1819      end
1820C>
1821C> @}
1822C>
1823C> \ingroup nwxc_priv
1824C> @{
1825C>
1826C> \brief The functional, 1st and 2nd order partial derivative evaluation
1827C> with AD
1828C>
1829C> In actual fact this routine only sets up the memory and then calls the
1830C> driver routine to drive the actual functional evaluation. The lack of
1831C> a Fortran90 typecast drives this code structure.
1832C>
1833      subroutine nwxca_eval_df2(ipol,nq,rho,gamma,tau,f,dfdr,dfdr2,
1834     +                          dfdg,dfdg2,dfdt,dfdt2)
1835      use nwad2
1836      implicit none
1837#include "errquit.fh"
1838#include "mafdecls.fh"
1839#include "nwxc_param.fh"
1840      integer ipol !< [Input] The number of spin channels
1841      integer nq   !< [Input] The number of points
1842C
1843      double precision rho(nq,ipol)     !< [Input] Density
1844      double precision gamma(nq,ipol+1) !< [Input] |Density gradient|^2
1845      double precision tau(nq,ipol)     !< [Input] Kinetic energy
1846                                        !< density
1847C
1848      double precision f(nq)           !< [Output] Energy
1849      double precision dfdr(nq,ipol)   !< [Output] Derivative wrt rho
1850      double precision dfdg(nq,ipol+1) !< [Output] Derivative wrt gamma
1851      double precision dfdt(nq,ipol)   !< [Output] Derivative wrt tau
1852      double precision dfdr2(nq,NCOL_AMAT2) !< [Output] 2nd derivative wrt rho
1853      double precision dfdg2(nq,NCOL_CMAT2) !< [Output] 2nd derivative wrt gamma
1854      double precision dfdt2(nq,NCOL_MMAT2) !< [Output] 2nd derivative wrt tau
1855c
1856      type(nwad_dble) :: memory_test_nwad(2)
1857      double precision   memory_test_dble(2)
1858      integer length
1859      integer l_rho, k_rho !< Index for density
1860      integer l_gam, k_gam !< Index for gradient
1861      integer l_tau, k_tau !< Index for kinetic energy density
1862      integer l_fun, k_fun !< Index for functional
1863      integer l_scr, k_scr !< Index for scratch
1864      integer nvar         !< The number of variables in the functional
1865                           !< LDA: nvar=ipol, GGA: nvar=2*ipol+1,
1866                           !< MGGA: nvar=3*ipol+1
1867      integer ndrv         !< The number of partial derivatives
1868      integer ipl          !< Hack version of ipol
1869C
1870      logical nwxc_is_gga  !< Is the functional a GGA
1871      logical nwxc_is_mgga !< Is the functional a meta-GGA
1872c
1873c     Work out nvar for this functional
1874c
1875      ipl = 2
1876      nvar = 2
1877      if (nwxc_is_gga().or.nwxc_is_mgga()) then
1878        nvar = nvar + 3
1879        if (nwxc_is_mgga()) then
1880          nvar = nvar + 2
1881        endif
1882      endif
1883      ndrv = nvar*(nvar+1)/2
1884c
1885c     Work out how many double precision floating point words are needed
1886c     to represent a single nwad_dble
1887c
1888      length = (loc(memory_test_dble(2))-loc(memory_test_dble(1)))
1889      length = (loc(memory_test_nwad(2))-loc(memory_test_nwad(1))
1890     +          +length-1)/length
1891      if(.not.ma_push_get(mt_dbl,length*nq*ipl,"nwad rho",l_rho,k_rho))
1892     +  call errquit("nwxca_eval_df2: cannot allocate nwad rho",
1893     +    ma_sizeof(mt_dbl,length*nq*ipl,mt_byte),MA_ERR)
1894      if(.not.ma_push_get(mt_dbl,length*nq*(ipl+1),"nwad gamma",
1895     +                    l_gam,k_gam))
1896     +  call errquit("nwxca_eval_df2: cannot allocate nwad gamma",
1897     +    ma_sizeof(mt_dbl,length*nq*(ipl+1),mt_byte),MA_ERR)
1898      if(.not.ma_push_get(mt_dbl,length*nq*ipl,"nwad tau",l_tau,k_tau))
1899     +  call errquit("nwxca_eval_df2: cannot allocate nwad tau",
1900     +    ma_sizeof(mt_dbl,length*nq*ipl,mt_byte),MA_ERR)
1901      if(.not.ma_push_get(mt_dbl,length*nq*ndrv,"nwad fun",l_fun,k_fun))
1902     +  call errquit("nwxca_eval_df2: cannot allocate nwad fun",
1903     +    ma_sizeof(mt_dbl,length*nq*ndrv,mt_byte),MA_ERR)
1904c
1905      call nwxc_eval_df2_driver(ipol,nq,length,rho,gamma,tau,
1906     +     dbl_mb(k_rho),dbl_mb(k_gam),dbl_mb(k_tau),dbl_mb(k_fun),
1907     +     nvar,ndrv,f,dfdr,dfdr2,dfdg,dfdg2,dfdt,dfdt2)
1908c
1909      if(.not.ma_pop_stack(l_fun)) call errquit(
1910     +  "nwxca_eval_df2: cannot deallocate nwad fun",0,MA_ERR)
1911      if(.not.ma_pop_stack(l_tau)) call errquit(
1912     +  "nwxca_eval_df2: cannot deallocate nwad tau",0,MA_ERR)
1913      if(.not.ma_pop_stack(l_gam)) call errquit(
1914     +  "nwxca_eval_df2: cannot deallocate nwad gam",0,MA_ERR)
1915      if(.not.ma_pop_stack(l_rho)) call errquit(
1916     +  "nwxca_eval_df2: cannot deallocate nwad rho",0,MA_ERR)
1917      end
1918C>
1919C> \brief Driver routine for the functional, 1st and 2nd derivative evaluation
1920C>
1921C> This driver routine initializes the active variables and invokes the
1922C> functional evaluation. After the functional has been evaluated the results
1923C> are unpacked and stored in the appropriate arrays.
1924C>
1925C> An issue the first arises in calculating the 2nd derivatives is related
1926C> to how spin can be handled in closed shell calculations. For some properties
1927C> the energy expression can be cast in a spin free form. In those cases one
1928C> can just calculate the derivatives wrt. the total density, the total density
1929C> gradient and the total kinetic energy density. However, there are also
1930C> quantities such as the energy of a triplet excited state from a closed
1931C> shell ground state. In this case the excitation energy is an explicitly spin
1932C> dependent quantity evaluated at equal \f$\alpha\f$ and \f$\beta\f$ spin
1933C> densities. Evaluating this energy expression requires explicit knowledge
1934C> of the cross terms involving different spin channels.
1935C>
1936C> Here automatic differentiation has a disadvantage compared to symbolic
1937C> algebra. In symbolic algebra one can derive the relevant partial derivatives
1938C> and subsequently substitute that \f$\rho_\alpha\f$ equals \f$\rho_\beta\f$
1939C> allowing for significant simplification of the expressions to be evaluated.
1940C> In automatic differentiation, on the other hand, working out the form of
1941C> the derivative expression and evaluating it are one and the same thing.
1942C> Therefore if you want to calculate cross terms between spin channels you
1943C> have to treat them as separate variables. Essentially you have to deal with
1944C> the equations as the unrestricted open-shell case. So there are no savings
1945C> to be had from exploiting that the \f$\alpha\f$ and \f$\beta\f$ densities
1946C> are the same.
1947C>
1948C> In practice, therefore, this code will perform a slightly different
1949C> initialization depending on whether we are running a closed shell or
1950C> open shell calculation, but the functional evaluation is executed as if
1951C> it is an open shell calculation. Also the data is unpacked as if it is
1952C> an open shell calculation.
1953C>
1954      subroutine nwxc_eval_df2_driver(ipol,nq,ndbl,rho,gamma,tau,
1955     +           nwad_rho,nwad_gam,nwad_tau,nwad_f,nvar,ndrv,
1956     +           f,dfdr,dfdr2,dfdg,dfdg2,dfdt,dfdt2)
1957      use nwad2
1958      implicit none
1959#include "errquit.fh"
1960#include "nwxc_param.fh"
1961      integer ipol !< [Input] The number of spin channels
1962      integer nq   !< [Input] The number of points
1963      integer ndbl !< [Input] The number doubles per nwad_dble
1964      integer nvar !< [Input] The number of independent variables
1965      integer ndrv !< [Input] The number of 2nd order partial derivatives
1966C
1967      double precision rho(nq,ipol)     !< [Input] Density
1968      double precision gamma(nq,ipol+1) !< [Input] |Density gradient|^2
1969      double precision tau(nq,ipol)     !< [Input] Kinetic energy
1970                                         !< density
1971C
1972      double precision f(nq)           !< [Output] Energy
1973      double precision dfdr(nq,ipol)   !< [Output] Derivative wrt rho
1974      double precision dfdg(nq,ipol+1) !< [Output] Derivative wrt gamma
1975      double precision dfdt(nq,ipol)   !< [Output] Derivative wrt tau
1976      double precision dfdr2(nq,NCOL_AMAT2) !< [Output] 2nd derivative wrt rho
1977      double precision dfdg2(nq,NCOL_CMAT2) !< [Output] 2nd derivative wrt gamma
1978      double precision dfdt2(nq,NCOL_MMAT2) !< [Output] 2nd derivative wrt tau
1979c
1980      type(nwad_dble) :: nwad_rho(nq,2)
1981      type(nwad_dble) :: nwad_gam(nq,3)
1982      type(nwad_dble) :: nwad_tau(nq,2)
1983      type(nwad_dble) :: nwad_f(nq)
1984      type(nwad_dble) :: nwad_scr(nq)
1985C
1986      logical nwxc_is_gga  !< Is the functional a GGA
1987      logical nwxc_is_mgga !< Is the functional a meta-GGA
1988c
1989      integer iq
1990      integer ix1, ix2
1991      integer iv1, iv2
1992c
1993      double precision val
1994c
1995c     Scaling factors to convert
1996c     - df/drho,
1997c     - df/dgamma and
1998c     - df/dtau
1999c     to the quantities NWChem expects, i.e.
2000c     - df/drhoa
2001c     - df/dgammaaa+1/2*df/dgammaab
2002c     - df/dta
2003c
2004c     For the second derivatives
2005c     - d2f/drho2
2006c     - d2f/drhodgamma
2007c     - d2f/dgamma2
2008c     - d2f/drhodtau
2009c     - d2f/dgammadtau
2010c     - d2f/dtau2
2011c     to the quantities NWChems expects, i.e.
2012c     - d2f/drhoa2+d2f/drhoadrhob
2013c     - d2f/drhoadgammaaa+d2f/drhoadgammaab+d2f/drhoadgammabb
2014c     - d2f/dgammaaa2+d2f/dgammaaadgammaab+d2f/dgammaaadgammabb
2015c       +d2f/dgammaab2
2016c     - d2f/drhoadtaua+d2f/drhoadtaub
2017c     - d2f/dgammaaadtaua+d2f/dgammaabdtaua+d2f/dgammabbdtaua
2018c     - d2f/dtaua2+d2f/dtauadtaub
2019c
2020      double precision sfac_ra  !< the closed shell RA scaling factor
2021      double precision sfac_gaa !< the closed shell GAA scaling factor
2022      double precision sfac_ta  !< the closed shell TA scaling factor
2023      parameter(sfac_ra  = 1.0d0)
2024      parameter(sfac_gaa = 2.0d0)
2025      parameter(sfac_ta  = 1.0d0)
2026      double precision sfac_rara   !< a closed shell scaling factor
2027      double precision sfac_ragaa  !< a closed shell scaling factor
2028      double precision sfac_gaagaa !< a closed shell scaling factor
2029      double precision sfac_rata   !< a closed shell scaling factor
2030      double precision sfac_gaata  !< a closed shell scaling factor
2031      double precision sfac_tata   !< a closed shell scaling factor
2032      parameter(sfac_rara   = 2.0d0)
2033      parameter(sfac_ragaa  = 4.0d0)
2034      parameter(sfac_gaagaa = 8.0d0)
2035      parameter(sfac_rata   = 2.0d0)
2036      parameter(sfac_gaata  = 4.0d0)
2037      parameter(sfac_tata   = 2.0d0)
2038c
2039      if (ipol.eq.1) then
2040        do iq = 1, nq
2041c         nwad_rho(iq,R_T) = set_rho_t(rho(iq,R_T))
2042          nwad_rho(iq,R_A) = set_rho_a(0.5d0*rho(iq,R_T))
2043          nwad_rho(iq,R_B) = set_rho_b(0.5d0*rho(iq,R_T))
2044        enddo
2045      else  ! ipol.eq.1
2046        do iq = 1, nq
2047          nwad_rho(iq,R_A) = set_rho_a(rho(iq,R_A))
2048        enddo
2049        do iq = 1, nq
2050          nwad_rho(iq,R_B) = set_rho_b(rho(iq,R_B))
2051        enddo
2052      endif ! ipol.eq.1
2053      if (nwxc_is_gga().or.nwxc_is_mgga()) then
2054        if (ipol.eq.1) then
2055          do iq = 1, nq
2056c           nwad_gam(iq,G_TT) = set_gamma_tt(gamma(iq,G_TT))
2057            nwad_gam(iq,G_AA) = set_gamma_aa(0.25d0*gamma(iq,G_TT))
2058            nwad_gam(iq,G_AB) = set_gamma_ab(0.25d0*gamma(iq,G_TT))
2059            nwad_gam(iq,G_BB) = set_gamma_bb(0.25d0*gamma(iq,G_TT))
2060          enddo
2061        else  ! ipol.eq.1
2062          do iq = 1, nq
2063            nwad_gam(iq,G_AA) = set_gamma_aa(gamma(iq,G_AA))
2064          enddo
2065          do iq = 1, nq
2066            nwad_gam(iq,G_AB) = set_gamma_ab(gamma(iq,G_AB))
2067          enddo
2068          do iq = 1, nq
2069            nwad_gam(iq,G_BB) = set_gamma_bb(gamma(iq,G_BB))
2070          enddo
2071        endif ! ipol.eq.1
2072      endif
2073      if (nwxc_is_mgga()) then
2074        if (ipol.eq.1) then
2075          do iq = 1, nq
2076c           nwad_tau(iq,T_T) = set_tau_t(tau(iq,T_T))
2077            nwad_tau(iq,T_A) = set_tau_a(0.5d0*tau(iq,T_T))
2078            nwad_tau(iq,T_B) = set_tau_b(0.5d0*tau(iq,T_T))
2079          enddo
2080        else  ! ipol.eq.1
2081          do iq = 1, nq
2082            nwad_tau(iq,T_A) = set_tau_a(tau(iq,T_A))
2083          enddo
2084          do iq = 1, nq
2085            nwad_tau(iq,T_B) = set_tau_b(tau(iq,T_B))
2086          enddo
2087        endif ! ipol.eq.1
2088      endif
2089c
2090      call nwxc_eval_df2_doit(2,nq,nwad_rho,nwad_gam,
2091     +     nwad_tau,nwad_f,dfdr,dfdg,dfdt)
2092c
2093c     Now unpack the results
2094c
2095      if (.false..and.ipol.eq.1) then
2096c
2097c       Closed shell case -> use splitting factors
2098c
2099        do iq = 1, nq
2100          f(iq) = get_val(nwad_f(iq))
2101          nvar = get_nvar(nwad_f(iq))
2102          do ix1 = 1, nvar
2103            call get_d1(nwad_f(iq),ix1,val,iv1)
2104            select case (iv1)
2105              case (1)
2106                dfdr(iq,D1_RA)  = val*sfac_ra
2107              case (3)
2108                dfdg(iq,D1_GAA) = val*sfac_gaa
2109                dfdg(iq,D1_GAB) = 0.0d0
2110              case (6)
2111                dfdt(iq,D1_TA)  = val*sfac_ta
2112              case default
2113                call errquit("nwxc_df2_driver: get_d1: "
2114     +                     //"illegal variable",iv1,UERR)
2115            end select
2116            do ix2 = 1, ix1
2117              call get_d2(nwad_f(iq),ix1,ix2,val,iv1,iv2)
2118              select case (iv1)
2119                case (1)
2120                  select case (iv2)
2121                    case (1)
2122                      dfdr2(iq,D2_RA_RA) = val*sfac_rara
2123                      dfdr2(iq,D2_RA_RB) = 0.0d0
2124                  end select
2125                case (3)
2126                  select case (iv2)
2127                    case (1)
2128                      dfdg2(iq,D2_RA_GAA)  = val*sfac_ragaa
2129                      dfdg2(iq,D2_RA_GAB)  = 0.0d0
2130                      dfdg2(iq,D2_RA_GBB)  = 0.0d0
2131                    case (3)
2132                      dfdg2(iq,D2_GAA_GAA) = val*sfac_gaagaa
2133                      dfdg2(iq,D2_GAA_GAB) = 0.0d0
2134                      dfdg2(iq,D2_GAA_GBB) = 0.0d0
2135                      dfdg2(iq,D2_GAB_GAB) = 0.0d0
2136                  end select
2137                case (6)
2138                  select case (iv2)
2139                    case (1)
2140                      dfdt2(iq,D2_RA_TA)  = val*sfac_rata
2141                      dfdt2(iq,D2_RA_TB)  = 0.0d0
2142                    case (3)
2143                      dfdt2(iq,D2_GAA_TA) = val*sfac_gaata
2144                      dfdt2(iq,D2_GAB_TA) = 0.0d0
2145                      dfdt2(iq,D2_GBB_TA) = 0.0d0
2146                    case (6)
2147                      dfdt2(iq,D2_TA_TA)  = val*sfac_tata
2148                      dfdt2(iq,D2_TA_TB)  = 0.0d0
2149                  end select
2150                case default
2151                  call errquit("nwxc_df2_driver: get_d2: "//
2152     &                         "illegal variable",iv1,UERR)
2153              end select
2154            enddo
2155          enddo
2156        enddo
2157c
2158      else
2159c
2160c       Unrestricted open shell case -> plain unpacking
2161c
2162        do iq = 1, nq
2163          f(iq) = get_val(nwad_f(iq))
2164          nvar = get_nvar(nwad_f(iq))
2165          do ix1 = 1, nvar
2166            call get_d1(nwad_f(iq),ix1,val,iv1)
2167            select case (iv1)
2168              case (1)
2169                dfdr(iq,D1_RA) = val
2170              case (2)
2171                dfdr(iq,D1_RB) = val
2172              case (3)
2173                dfdg(iq,D1_GAA) = val
2174              case (4)
2175                dfdg(iq,D1_GAB) = val
2176              case (5)
2177                dfdg(iq,D1_GBB) = val
2178              case (6)
2179                dfdt(iq,D1_TA) = val
2180              case (7)
2181                dfdt(iq,D1_TB) = val
2182              case default
2183                call errquit("nwxc_df2_driver: get_d1: "
2184     +                     //"illegal variable",iv1,UERR)
2185            end select
2186            do ix2 = 1, ix1
2187              call get_d2(nwad_f(iq),ix1,ix2,val,iv1,iv2)
2188              select case (iv1)
2189                case (1)
2190                  select case (iv2)
2191                    case (1)
2192                      dfdr2(iq,D2_RA_RA) = val
2193                  end select
2194                case (2)
2195                  select case (iv2)
2196                    case (1)
2197                      dfdr2(iq,D2_RA_RB) = val
2198                    case (2)
2199                      dfdr2(iq,D2_RB_RB) = val
2200                  end select
2201                case (3)
2202                  select case (iv2)
2203                    case (1)
2204                      dfdg2(iq,D2_RA_GAA) = val
2205                    case (2)
2206                      dfdg2(iq,D2_RB_GAA) = val
2207                    case (3)
2208                      dfdg2(iq,D2_GAA_GAA) = val
2209                  end select
2210                case (4)
2211                  select case (iv2)
2212                    case (1)
2213                      dfdg2(iq,D2_RA_GAB) = val
2214                    case (2)
2215                      dfdg2(iq,D2_RB_GAB) = val
2216                    case (3)
2217                      dfdg2(iq,D2_GAA_GAB) = val
2218                    case (4)
2219                      dfdg2(iq,D2_GAB_GAB) = val
2220                  end select
2221                case (5)
2222                  select case (iv2)
2223                    case (1)
2224                      dfdg2(iq,D2_RA_GBB) = val
2225                    case (2)
2226                      dfdg2(iq,D2_RB_GBB) = val
2227                    case (3)
2228                      dfdg2(iq,D2_GAA_GBB) = val
2229                    case (4)
2230                      dfdg2(iq,D2_GAB_GBB) = val
2231                    case (5)
2232                      dfdg2(iq,D2_GBB_GBB) = val
2233                  end select
2234                case (6)
2235                  select case (iv2)
2236                    case (1)
2237                      dfdt2(iq,D2_RA_TA) = val
2238                    case (2)
2239                      dfdt2(iq,D2_RB_TA) = val
2240                    case (3)
2241                      dfdt2(iq,D2_GAA_TA) = val
2242                    case (4)
2243                      dfdt2(iq,D2_GAB_TA) = val
2244                    case (5)
2245                      dfdt2(iq,D2_GBB_TA) = val
2246                    case (6)
2247                      dfdt2(iq,D2_TA_TA) = val
2248                  end select
2249                case (7)
2250                  select case (iv2)
2251                    case (1)
2252                      dfdt2(iq,D2_RA_TB) = val
2253                    case (2)
2254                      dfdt2(iq,D2_RB_TB) = val
2255                    case (3)
2256                      dfdt2(iq,D2_GAA_TB) = val
2257                    case (4)
2258                      dfdt2(iq,D2_GAB_TB) = val
2259                    case (5)
2260                      dfdt2(iq,D2_GBB_TB) = val
2261                    case (6)
2262                      dfdt2(iq,D2_TA_TB) = val
2263                    case (7)
2264                      dfdt2(iq,D2_TB_TB) = val
2265                  end select
2266                case default
2267                  call errquit("nwxc_df2_driver: get_d2: "//
2268     &                         "illegal variable",iv1,UERR)
2269              end select
2270            enddo
2271          enddo
2272        enddo
2273c
2274      endif
2275c
2276      end
2277C>
2278C> \brief Evaluate the exchange-correlation energy and its 1st and 2nd
2279C> partial derivatives
2280C>
2281      subroutine nwxc_eval_df2_doit(ipol,nq,rho,gamma,tau,f,dfdr,dfdr2,
2282     +                         dfdg,dfdg2,dfdt,dfdt2)
2283      use nwad2
2284      implicit none
2285#include "nwxcP.fh"
2286#include "nwxc_param.fh"
2287      integer ipol !< [Input] The number of spin channels
2288      integer nq   !< [Input] The number of points
2289C
2290      type(nwad_dble)::rho(nq,ipol)     !< [Input] Density
2291      type(nwad_dble)::gamma(nq,ipol+1) !< [Input] |Density gradient|^2
2292      type(nwad_dble)::tau(nq,ipol)     !< [Input] Kinetic energy
2293                                        !< density
2294C
2295      type(nwad_dble)::f(nq)           !< [Output] Energy
2296      double precision dfdr(nq,ipol)   !< [Output] Derivative wrt rho
2297      double precision dfdg(nq,ipol+1) !< [Output] Derivative wrt gamma
2298      double precision dfdt(nq,ipol)   !< [Output] Derivative wrt tau
2299c
2300      double precision dfdr2(nq,*)     !< [Output] 2nd derivative wrt
2301                                       !< rho
2302      double precision dfdg2(nq,*)     !< [Output] 2nd derivative wrt
2303                                       !< rho and gamma, and gamma
2304      double precision dfdt2(nq,*)     !< [Output] 2nd derivative wrt
2305                                       !< rho and tau, gamma and tau,
2306                                       !< and tau
2307C
2308      integer iq !< Counter over points
2309      integer ip !< Counter over spin channels
2310      integer it !< Counter of functional terms
2311      integer n  !< Counter
2312C
2313      logical nwxc_is_gga  !< Is the functional a GGA
2314      logical nwxc_is_mgga !< Is the functional a meta-GGA
2315C
2316      integer nd1r(2) !< The number of partial derivatives wrt rho as
2317                      !< a function of ipol
2318      integer nd1g(2) !< The number of partial derivatives wrt gamma as
2319                      !< a function of ipol
2320      integer nd1t(2) !< The number of partial derivatives wrt tau as
2321                      !< a function of ipol
2322      integer nd2r(2) !< The number of 2nd partial derivatives wrt rho
2323                      !< as a function of ipol
2324      integer nd2g(2) !< The number of 2nd partial derivatives wrt
2325                      !< gamma as a function of ipol
2326      integer nd2t(2) !< The number of 2nd partial derivatives wrt tau
2327                      !< as a function of ipol
2328C
2329      external nwxc_k_dirac_d2
2330      external nwxc_k_becke88_d2
2331      external nwxc_k_pbe96_d2
2332c
2333      integer max_param
2334      parameter (max_param = 50)
2335      double precision param(max_param)
2336      double precision Axlsda
2337      parameter (Axlsda = -0.9305257363491d0 )
2338C
2339      data nd1r / D1_RA,  D1_RB  /
2340      data nd1g / D1_GAA, D1_GBB /
2341      data nd1t / D1_TA,  D1_TB  /
2342C
2343      data nd2r / D2_RA_RA,   D2_RB_RB  /
2344c      data nd2g / D2_GAA_GAA, D2_GBB_GBB /
2345      data nd2g / D2_GAA_GBB, D2_GBB_GBB /
2346      data nd2t / D2_TA_TA,   D2_TB_TB  /
2347C
2348      do iq = 1, nq
2349        f(iq) = 0.0d0
2350      enddo
2351C
2352      do it = 1, nwxc_num_f
2353        select case (nwxc_ids(it))
2354          case (NWXCP_X_SLATER)
2355            call nwxc_x_dirac_d2(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
2356     +                           rho,f)
2357          case (NWXCP_X_B86b)
2358            call nwxc_x_b86b_d2(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
2359     +                          rho,gamma,f)
2360          case (NWXCP_X_B88)
2361            call nwxc_x_b88_d2(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
2362     +                         rho,gamma,f)
2363          case (NWXCP_X_B97)
2364            param(1) = 2.0d0
2365            param(2) = 0.80940d+00
2366            param(3) = 0.50730d+00
2367            param(4) = 0.74810d+00
2368            call nwxc_x_b97_d2(param,nwxc_rho_tol,ipol,nq,
2369     +                         nwxc_wghts(it),rho,gamma,f)
2370          case (NWXCP_X_B97_1)
2371            param(1) = 2.0d0
2372            param(2) = 0.789518d+00
2373            param(3) = 0.573805d+00
2374            param(4) = 0.660975d+00
2375            call nwxc_x_b97_d2(param,nwxc_rho_tol,ipol,nq,
2376     +                         nwxc_wghts(it),rho,gamma,f)
2377          case (NWXCP_X_B97_2)
2378            param(1) = 2.0d0
2379            param(2) = 0.827642D+00
2380            param(3) = 0.478400D-01
2381            param(4) = 0.176125D+01
2382            call nwxc_x_b97_d2(param,nwxc_rho_tol,ipol,nq,
2383     +                         nwxc_wghts(it),rho,gamma,f)
2384          case (NWXCP_X_B97_3)
2385            param(1) = 4.0d0
2386            param(2) = 7.334648D-01
2387            param(3) = 2.925270D-01
2388            param(4) = 3.338789D+00
2389            param(5) =-1.051158D+01
2390            param(6) = 1.060907D+01
2391            call nwxc_x_b97_d2(param,nwxc_rho_tol,ipol,nq,
2392     +                         nwxc_wghts(it),rho,gamma,f)
2393          case (NWXCP_X_B97_D)
2394            param(1) = 2.0d0
2395            param(2) = 1.086620d+0
2396            param(3) =-0.521270d+00
2397            param(4) = 3.254290d+00
2398            call nwxc_x_b97_d2(param,nwxc_rho_tol,ipol,nq,
2399     +                         nwxc_wghts(it),rho,gamma,f)
2400          case (NWXCP_X_B97_G)
2401            param(1) = 2.0d0
2402            param(2) = 1.1068d0
2403            param(3) =-0.8765d0
2404            param(4) = 4.2639d0
2405            call nwxc_x_b97_d2(param,nwxc_rho_tol,ipol,nq,
2406     +                         nwxc_wghts(it),rho,gamma,f)
2407          case (NWXCP_X_B98)
2408            param(1) = 2.0d0
2409            param(2) = 0.790194d00
2410            param(3) = 0.400271d00
2411            param(4) = 0.832857d00
2412            call nwxc_x_b97_d2(param,nwxc_rho_tol,ipol,nq,
2413     +                         nwxc_wghts(it),rho,gamma,f)
2414          case (NWXCP_X_BNL)
2415            param(1) = nwxc_cam_gamma
2416            call nwxc_x_bnl_d2(param,nwxc_rho_tol,ipol,nq,
2417     +                         nwxc_wghts(it),rho,f)
2418          case (NWXCP_X_CAMB88)
2419            param(1) = nwxc_cam_alpha
2420            param(2) = nwxc_cam_beta
2421            param(3) = nwxc_cam_gamma
2422            call nwxc_x_camb88_d2(param,nwxc_rho_tol,ipol,nq,
2423     +                            nwxc_wghts(it),rho,gamma,f)
2424          case (NWXCP_X_CAMLSD)
2425            param(1) = nwxc_cam_alpha
2426            param(2) = nwxc_cam_beta
2427            param(3) = nwxc_cam_gamma
2428            call nwxc_x_camlsd_d2(param,nwxc_rho_tol,ipol,nq,
2429     +                            nwxc_wghts(it),rho,f)
2430          case (NWXCP_X_CAMPBE)
2431            param(1) = 0.8040d0
2432            param(2) = 0.2195149727645171d0
2433            param(3) = nwxc_cam_alpha
2434            param(4) = nwxc_cam_beta
2435            param(5) = nwxc_cam_gamma
2436            call nwxc_x_campbe_d2(param,nwxc_rho_tol,ipol,nq,
2437     +                            nwxc_wghts(it),rho,gamma,f)
2438          case (NWXCP_X_CAMREVPBE)
2439            param(1) = 1.245d0
2440            param(2) = 0.2195149727645171d0
2441            param(3) = nwxc_cam_alpha
2442            param(4) = nwxc_cam_beta
2443            param(5) = nwxc_cam_gamma
2444            call nwxc_x_campbe_d2(param,nwxc_rho_tol,ipol,nq,
2445     +                            nwxc_wghts(it),rho,gamma,f)
2446          case (NWXCP_X_CAMRPBE)
2447            param(1) = nwxc_cam_alpha
2448            param(2) = nwxc_cam_beta
2449            param(3) = nwxc_cam_gamma
2450            call nwxc_x_camrpbe_d2(param,nwxc_rho_tol,ipol,nq,
2451     +                             nwxc_wghts(it),rho,gamma,f)
2452          case (NWXCP_X_CAMS12G)
2453            param(1) = 1.03323556d0
2454            param(2) = 0.757d0
2455            param(3) = 0.00417251d0
2456            param(4) = 0.00115216d0
2457            param(5) = 0.00706184d0
2458            param(6) = nwxc_cam_alpha
2459            param(7) = nwxc_cam_beta
2460            param(8) = nwxc_cam_gamma
2461            call nwxc_x_cams12_d2(param,nwxc_rho_tol,ipol,nq,
2462     +                            nwxc_wghts(it),rho,gamma,f)
2463          case (NWXCP_X_CAMS12H)
2464            param(1) = 1.02149642d0
2465            param(2) = 0.757d0
2466            param(3) = 0.00825905d0
2467            param(4) = 0.00235804d0
2468            param(5) = 0.00654977d0
2469            param(6) = nwxc_cam_alpha
2470            param(7) = nwxc_cam_beta
2471            param(8) = nwxc_cam_gamma
2472            call nwxc_x_cams12_d2(param,nwxc_rho_tol,ipol,nq,
2473     +                            nwxc_wghts(it),rho,gamma,f)
2474           case (NWXCP_X_DLDF)
2475             call nwxc_x_dldf_d2(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
2476     +            rho,gamma,tau,f)
2477          case (NWXCP_X_FT97)
2478            call nwxc_x_ft97_d2(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
2479     +                          rho,gamma,f)
2480          case (NWXCP_X_GILL)
2481            call nwxc_x_gill_d2(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
2482     +                          rho,gamma,f)
2483          case (NWXCP_X_HCTH)
2484            param(1) = 4.0d0
2485            param(2) = 0.109320d+01
2486            param(3) =-0.744056d+00
2487            param(4) = 0.559920d+01
2488            param(5) =-0.678549d+01
2489            param(6) = 0.449357d+01
2490            call nwxc_x_b97_d2(param,nwxc_rho_tol,ipol,nq,
2491     +                         nwxc_wghts(it),rho,gamma,f)
2492          case (NWXCP_X_HCTH120)
2493            param(1) = 4.0d0
2494            param(2) = 1.09163d0
2495            param(3) =-0.74720d0
2496            param(4) = 5.07830d0
2497            param(5) =-4.10750d0
2498            param(6) = 1.17170d0
2499            call nwxc_x_b97_d2(param,nwxc_rho_tol,ipol,nq,
2500     +                         nwxc_wghts(it),rho,gamma,f)
2501          case (NWXCP_X_HCTH147)
2502            param(1) = 4.0d0
2503            param(2) = 1.09025d0
2504            param(3) =-0.79920d0
2505            param(4) = 5.57210d0
2506            param(5) =-5.86760d0
2507            param(6) = 3.04540d0
2508            call nwxc_x_b97_d2(param,nwxc_rho_tol,ipol,nq,
2509     +                         nwxc_wghts(it),rho,gamma,f)
2510          case (NWXCP_X_HCTH407)
2511            param(1) = 4.0d0
2512            param(2) = 1.08184d0
2513            param(3) =-0.5183d0
2514            param(4) = 3.4256d0
2515            param(5) =-2.6290d0
2516            param(6) = 2.2886d0
2517            call nwxc_x_b97_d2(param,nwxc_rho_tol,ipol,nq,
2518     +                         nwxc_wghts(it),rho,gamma,f)
2519          case (NWXCP_X_HCTH407P)
2520            param(1) = 4.0d0
2521            param(2) = 1.08018D0
2522            param(3) =-0.4117D0
2523            param(4) = 2.4368D0
2524            param(5) = 1.3890D0
2525            param(6) =-1.3529D0
2526            call nwxc_x_b97_d2(param,nwxc_rho_tol,ipol,nq,
2527     +                         nwxc_wghts(it),rho,gamma,f)
2528          case (NWXCP_X_HCTH_A)
2529            param(1) = 2.0d0
2530            param(2) = 0.109878d+01
2531            param(3) =-0.251173d+01
2532            param(4) = 0.156233d-01
2533            call nwxc_x_b97_d2(param,nwxc_rho_tol,ipol,nq,
2534     +                         nwxc_wghts(it),rho,gamma,f)
2535          case (NWXCP_X_HCTHP14)
2536            param(1) = 4.0d0
2537            param(2) = 0.103161d+01
2538            param(3) =-0.360781d+00
2539            param(4) = 0.351994d+01
2540            param(5) =-0.495944d+01
2541            param(6) = 0.241165d+01
2542            call nwxc_x_b97_d2(param,nwxc_rho_tol,ipol,nq,
2543     +                         nwxc_wghts(it),rho,gamma,f)
2544           case (NWXCP_X_M05)
2545             param( 1) =    0.08151d0
2546             param( 2) =   -0.43956d0
2547             param( 3) =   -3.22422d0
2548             param( 4) =    2.01819d0
2549             param( 5) =    8.79431d0
2550             param( 6) =   -0.00295d0
2551             param( 7) =    9.82029d0
2552             param( 8) =   -4.82351d0
2553             param( 9) =  -48.17574d0
2554             param(10) =    3.64802d0
2555             param(11) =   34.02248d0
2556             call nwxc_x_m05_d2(param,nwxc_rho_tol,ipol,nq,
2557     +            nwxc_wghts(it),rho,gamma,tau,f)
2558           case (NWXCP_X_M05_2X)
2559             param( 1) =   -0.56833d0
2560             param( 2) =   -1.30057d0
2561             param( 3) =    5.50070d0
2562             param( 4) =    9.06402d0
2563             param( 5) =  -32.21075d0
2564             param( 6) =  -23.73298d0
2565             param( 7) =   70.22996d0
2566             param( 8) =   29.88614d0
2567             param( 9) =  -60.25778d0
2568             param(10) =  -13.22205d0
2569             param(11) =   15.23694d0
2570             call nwxc_x_m05_d2(param,nwxc_rho_tol,ipol,nq,
2571     +            nwxc_wghts(it),rho,gamma,tau,f)
2572           case (NWXCP_X_M06)
2573             param( 1) =  1.422057D-01*Axlsda
2574             param( 2) =  7.370319D-04*Axlsda
2575             param( 3) = -1.601373D-02*Axlsda
2576             param( 4) =  0.000000D+00
2577             param( 5) =  0.000000D+00
2578             param( 6) =  0.000000D+00
2579             param( 7) =  5.877943D-01
2580             param( 8) = -1.371776D-01
2581             param( 9) =  2.682367D-01
2582             param(10) = -2.515898D+00
2583             param(11) = -2.978892D+00
2584             param(12) =  8.710679D+00
2585             param(13) =  1.688195D+01
2586             param(14) = -4.489724D+00
2587             param(15) = -3.299983D+01
2588             param(16) = -1.449050D+01
2589             param(17) =  2.043747D+01
2590             param(18) =  1.256504D+01
2591             call nwxc_x_m06_d2(param,nwxc_rho_tol,ipol,nq,
2592     +            nwxc_wghts(it),rho,gamma,tau,f)
2593           case (NWXCP_X_M06_HF)
2594             param( 1) = -1.179732D-01*Axlsda
2595             param( 2) = -2.500000D-03*Axlsda
2596             param( 3) = -1.180065D-02*Axlsda
2597             param( 4) =  0.000000D+00
2598             param( 5) =  0.000000D+00
2599             param( 6) =  0.000000D+00
2600             param( 7) =  1.179732D-01
2601             param( 8) = -1.066708D+00
2602             param( 9) = -1.462405D-01
2603             param(10) =  7.481848D+00
2604             param(11) =  3.776679D+00
2605             param(12) = -4.436118D+01
2606             param(13) = -1.830962D+01
2607             param(14) =  1.003903D+02
2608             param(15) =  3.864360D+01
2609             param(16) = -9.806018D+01
2610             param(17) = -2.557716D+01
2611             param(18) =  3.590404D+01
2612             call nwxc_x_m06_d2(param,nwxc_rho_tol,ipol,nq,
2613     +            nwxc_wghts(it),rho,gamma,tau,f)
2614           case (NWXCP_X_M06_L)
2615             param( 1) =  6.012244D-01*Axlsda
2616             param( 2) =  4.748822D-03*Axlsda
2617             param( 3) = -8.635108D-03*Axlsda
2618             param( 4) = -9.308062D-06*Axlsda
2619             param( 5) =  4.482811D-05*Axlsda
2620             param( 6) =  0.000000D+00
2621             param( 7) =  3.987756D-01
2622             param( 8) =  2.548219D-01
2623             param( 9) =  3.923994D-01
2624             param(10) = -2.103655D+00
2625             param(11) = -6.302147D+00
2626             param(12) =  1.097615D+01
2627             param(13) =  3.097273D+01
2628             param(14) = -2.318489D+01
2629             param(15) = -5.673480D+01
2630             param(16) =  2.160364D+01
2631             param(17) =  3.421814D+01
2632             param(18) = -9.049762D+00
2633             call nwxc_x_m06_d2(param,nwxc_rho_tol,ipol,nq,
2634     +            nwxc_wghts(it),rho,gamma,tau,f)
2635           case (NWXCP_X_M06_2X)
2636             param( 1) =  4.600000D-01
2637             param( 2) = -2.206052D-01
2638             param( 3) = -9.431788D-02
2639             param( 4) =  2.164494D+00
2640             param( 5) = -2.556466D+00
2641             param( 6) = -1.422133D+01
2642             param( 7) =  1.555044D+01
2643             param( 8) =  3.598078D+01
2644             param( 9) = -2.722754D+01
2645             param(10) = -3.924093D+01
2646             param(11) =  1.522808D+01
2647             param(12) =  1.522227D+01
2648             call nwxc_x_m06_2x_d2(param,nwxc_rho_tol,ipol,nq,
2649     +            nwxc_wghts(it),rho,gamma,tau,f)
2650           case (NWXCP_X_M08_HX)
2651c            parameters A
2652             param(01) =  1.3340172D+00
2653             param(02) = -9.4751087D+00
2654             param(03) = -1.2541893D+01
2655             param(04) =  9.1369974D+00
2656             param(05) =  3.4717204D+01
2657             param(06) =  5.8831807D+01
2658             param(07) =  7.1369574D+01
2659             param(08) =  2.3312961D+01
2660             param(09) =  4.8314679D+00
2661             param(10) = -6.5044167D+00
2662             param(11) = -1.4058265D+01
2663             param(12) =  1.2880570D+01
2664c            parameters B
2665             param(13) = -8.5631823D-01
2666             param(14) =  9.2810354D+00
2667             param(15) =  1.2260749D+01
2668             param(16) = -5.5189665D+00
2669             param(17) = -3.5534989D+01
2670             param(18) = -8.2049996D+01
2671             param(19) = -6.8586558D+01
2672             param(20) =  3.6085694D+01
2673             param(21) = -9.3740983D+00
2674             param(22) = -5.9731688D+01
2675             param(23) =  1.6587868D+01
2676             param(24) =  1.3993203D+01
2677c            parameters C and D
2678             do n = 25, 48
2679               param(n) = 0.0d0
2680             enddo
2681             call nwxc_x_m08_d2(param,nwxc_rho_tol,ipol,nq,
2682     +            nwxc_wghts(it),rho,gamma,tau,f)
2683           case (NWXCP_X_M08_SO)
2684c            parameters A
2685             param(01) = -3.4888428D-01
2686             param(02) = -5.8157416D+00
2687             param(03) =  3.7550810D+01
2688             param(04) =  6.3727406D+01
2689             param(05) = -5.3742313D+01
2690             param(06) = -9.8595529D+01
2691             param(07) =  1.6282216D+01
2692             param(08) =  1.7513468D+01
2693             param(09) = -6.7627553D+00
2694             param(10) =  1.1106658D+01
2695             param(11) =  1.5663545D+00
2696             param(12) =  8.7603470D+00
2697c            parameters B
2698             param(13) =  7.8098428D-01
2699             param(14) =  5.4538178D+00
2700             param(15) = -3.7853348D+01
2701             param(16) = -6.2295080D+01
2702             param(17) =  4.6713254D+01
2703             param(18) =  8.7321376D+01
2704             param(19) =  1.6053446D+01
2705             param(20) =  2.0126920D+01
2706             param(21) = -4.0343695D+01
2707             param(22) = -5.8577565D+01
2708             param(23) =  2.0890272D+01
2709             param(24) =  1.0946903D+01
2710c            parameters C and D
2711             do n = 25, 48
2712               param(n) = 0.0d0
2713             enddo
2714             call nwxc_x_m08_d2(param,nwxc_rho_tol,ipol,nq,
2715     +            nwxc_wghts(it),rho,gamma,tau,f)
2716           case (NWXCP_X_M11)
2717c            parameters A
2718             param(01) = -0.18399900D+00
2719             param(02) = -1.39046703D+01
2720             param(03) =  1.18206837D+01
2721             param(04) =  3.10098465D+01
2722             param(05) = -5.19625696D+01
2723             param(06) =  1.55750312D+01
2724             param(07) = -6.94775730D+00
2725             param(08) = -1.58465014D+02
2726             param(09) = -1.48447565D+00
2727             param(10) =  5.51042124D+01
2728             param(11) = -1.34714184D+01
2729             param(12) =  0.000000D+00
2730c            parameters B
2731             param(13) =  0.75599900D+00
2732             param(14) =  1.37137944D+01
2733             param(15) = -1.27998304D+01
2734             param(16) = -2.93428814D+01
2735             param(17) =  5.91075674D+01
2736             param(18) = -2.27604866D+01
2737             param(19) = -1.02769340D+01
2738             param(20) =  1.64752731D+02
2739             param(21) =  1.85349258D+01
2740             param(22) = -5.56825639D+01
2741             param(23) =  7.47980859D+00
2742             param(24) =  0.000000D+00
2743c            parameters C and D
2744             do n = 25, 48
2745               param(n) = 0.0d0
2746             enddo
2747             call nwxc_x_m11_d2(param,nwxc_rho_tol,ipol,nq,
2748     +            nwxc_wghts(it),rho,gamma,tau,f)
2749           case (NWXCP_X_M11_L)
2750c            parameters A
2751             param(01) =  8.121131D-01
2752             param(02) =  1.738124D+01
2753             param(03) =  1.154007D+00
2754             param(04) =  6.869556D+01
2755             param(05) =  1.016864D+02
2756             param(06) = -5.887467D+00
2757             param(07) =  4.517409D+01
2758             param(08) = -2.773149D+00
2759             param(09) = -2.617211D+01
2760             param(10) =  0.000000D+00
2761             param(11) =  0.000000D+00
2762             param(12) =  0.000000D+00
2763c            parameters B
2764             param(13) =  1.878869D-01
2765             param(14) = -1.653877D+01
2766             param(15) =  6.755753D-01
2767             param(16) = -7.567572D+01
2768             param(17) = -1.040272D+02
2769             param(18) =  1.831853D+01
2770             param(19) = -5.573352D+01
2771             param(20) = -3.520210D+00
2772             param(21) =  3.724276D+01
2773             param(22) =  0.000000D+00
2774             param(23) =  0.000000D+00
2775             param(24) =  0.000000D+00
2776c            parameters C
2777             param(25) = -4.386615D-01
2778             param(26) = -1.214016D+02
2779             param(27) = -1.393573D+02
2780             param(28) = -2.046649D+00
2781             param(29) =  2.804098D+01
2782             param(30) = -1.312258D+01
2783             param(31) = -6.361819D+00
2784             param(32) = -8.055758D-01
2785             param(33) =  3.736551D+00
2786             param(34) =  0.000000D+00
2787             param(35) =  0.000000D+00
2788             param(36) =  0.000000D+00
2789c            parameters D
2790             param(37) =  1.438662D+00
2791             param(38) =  1.209465D+02
2792             param(39) =  1.328252D+02
2793             param(40) =  1.296355D+01
2794             param(41) =  5.854866D+00
2795             param(42) = -3.378162D+00
2796             param(43) = -4.423393D+01
2797             param(44) =  6.844475D+00
2798             param(45) =  1.949541D+01
2799             param(46) =  0.000000D+00
2800             param(47) =  0.000000D+00
2801             param(48) =  0.000000D+00
2802             call nwxc_x_m11_d2(param,nwxc_rho_tol,ipol,nq,
2803     +            nwxc_wghts(it),rho,gamma,tau,f)
2804          case (NWXCP_X_MPW91)
2805            param(1) = 3.72d0
2806            param(2) = 0.00426D0
2807            call nwxc_x_pw91_d2(param,nwxc_rho_tol,ipol,nq,
2808     +                          nwxc_wghts(it),rho,gamma,f)
2809           case (NWXCP_X_OPT)
2810             call nwxc_x_opt_d2(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
2811     +                          rho,gamma,f)
2812          case (NWXCP_X_PW6B95)
2813            param(1) = 0.00538d0
2814            param(2) = 1.7382d0
2815            param(3) = 3.8901d0
2816            call nwxc_x_pw6_d2(param,nwxc_rho_tol,ipol,nq,
2817     +                         nwxc_wghts(it),rho,gamma,f)
2818          case (NWXCP_X_PWB6K)
2819            param(1) = 0.00539d0
2820            param(2) = 1.7077d0
2821            param(3) = 4.0876d0
2822            call nwxc_x_pw6_d2(param,nwxc_rho_tol,ipol,nq,
2823     +                         nwxc_wghts(it),rho,gamma,f)
2824          case (NWXCP_X_PW91)
2825            param(1) = 4.0d0
2826            param(2) = 0.0042D0
2827            call nwxc_x_pw91_d2(param,nwxc_rho_tol,ipol,nq,
2828     +                          nwxc_wghts(it),rho,gamma,f)
2829          case (NWXCP_X_PBE)
2830            param(1) = 0.8040d0
2831            param(2) = 0.2195149727645171d0
2832            call nwxc_x_pbe_d2(param,nwxc_rho_tol,ipol,nq,
2833     +                         nwxc_wghts(it),rho,gamma,f)
2834          case (NWXCP_X_PBESOL)
2835            param(1) = 0.8040d0
2836            param(2) = 10.0d0/81.0d0
2837            call nwxc_x_pbe_d2(param,nwxc_rho_tol,ipol,nq,
2838     +                         nwxc_wghts(it),rho,gamma,f)
2839          case (NWXCP_X_REVPBE)
2840            param(1) = 1.245d0
2841            param(2) = 0.2195149727645171d0
2842            call nwxc_x_pbe_d2(param,nwxc_rho_tol,ipol,nq,
2843     +                         nwxc_wghts(it),rho,gamma,f)
2844          case (NWXCP_X_RPBE)
2845            call nwxc_x_rpbe_d2(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
2846     +                          rho,gamma,f)
2847          case (NWXCP_X_PKZB)
2848            call nwxc_x_pkzb99_d2(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
2849     +                         rho,gamma,tau,f)
2850          case (NWXCP_X_S12G)
2851            param(1) = 1.03842032d0
2852            param(2) = 0.757d0
2853            param(3) = 0.00403198d0
2854            param(4) = 0.00104596d0
2855            param(5) = 0.00594635d0
2856            call nwxc_x_s12_d2(param,nwxc_rho_tol,ipol,nq,
2857     +                         nwxc_wghts(it),rho,gamma,f)
2858          case (NWXCP_X_S12H)
2859            param(1) = 1.02543951d0
2860            param(2) = 0.757d0
2861            param(3) = 0.00761554d0
2862            param(4) = 0.00211063d0
2863            param(5) = 0.00604672d0
2864            call nwxc_x_s12_d2(param,nwxc_rho_tol,ipol,nq,
2865     +                         nwxc_wghts(it),rho,gamma,f)
2866          case (NWXCP_X_SOGGA)
2867            param(1)  =  0.5d0
2868            param(2)  =  0.276d0
2869            param(3)  =  0.0d0
2870            param(4)  =  0.0d0
2871            param(5)  =  0.0d0
2872            param(6)  =  0.0d0
2873            param(7)  =  0.5d0
2874            param(8)  =  0.276d0
2875            param(9)  =  0.0d0
2876            param(10) =  0.0d0
2877            param(11) =  0.0d0
2878            param(12) =  0.0d0
2879            call nwxc_x_sogga_d2(param,nwxc_rho_tol,ipol,nq,
2880     +                           nwxc_wghts(it),rho,gamma,f)
2881          case (NWXCP_X_SOGGA11)
2882            param(1)  =  0.5d0
2883            param(2)  = -2.95535d0
2884            param(3)  =  15.7974d0
2885            param(4)  = -91.1804d0
2886            param(5)  =  96.2030d0
2887            param(6)  =  0.18683d0
2888            param(7)  =  0.50000d0
2889            param(8)  =  3.50743d0
2890            param(9)  = -12.9523d0
2891            param(10) =  49.7870d0
2892            param(11) = -33.2545d0
2893            param(12) = -11.1396d0
2894            call nwxc_x_sogga_d2(param,nwxc_rho_tol,ipol,nq,
2895     +                           nwxc_wghts(it),rho,gamma,f)
2896          case (NWXCP_X_SOGGA11_X)
2897            param(1)  =  2.99250d-01
2898            param(2)  =  3.21638d+00
2899            param(3)  = -3.55605d+00
2900            param(4)  =  7.65852d+00
2901            param(5)  = -1.12830d+01
2902            param(6)  =  5.25813d+00
2903            param(7)  =  2.99250d-01
2904            param(8)  = -2.88595d+00
2905            param(9)  =  3.23617d+00
2906            param(10) = -2.45393d+00
2907            param(11) = -3.75495d+00
2908            param(12) =  3.96613d+00
2909            call nwxc_x_sogga_d2(param,nwxc_rho_tol,ipol,nq,
2910     +                           nwxc_wghts(it),rho,gamma,f)
2911          case (NWXCP_X_SSB_D)
2912            call nwxc_x_ssbD_1_d2(nwxc_rho_tol,ipol,nq,
2913     +                            nwxc_wghts(it),rho,gamma,f)
2914          case (NWXCP_X_TPSS)
2915            call nwxc_x_tpss03_d2(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
2916     +                            rho,gamma,tau,f)
2917          case (NWXCP_X_WPBE)
2918            param(1) = nwxc_cam_gamma
2919            call nwxc_x_wpbe_d2(param,nwxc_rho_tol,ipol,nq,
2920     +                          nwxc_wghts(it),rho,gamma,f)
2921           case (NWXCP_X_VS98)
2922             param(1) =  -9.800683d-01
2923             param(2) =  -3.556788d-03
2924             param(3) =   6.250326d-03
2925             param(4) =  -2.354518d-05
2926             param(5) =  -1.282732d-04
2927             param(6) =   3.574822d-04
2928             call nwxc_x_vs98_d2(param,nwxc_rho_tol,ipol,nq,
2929     +            nwxc_wghts(it),rho,gamma,tau,f)
2930          case (NWXCP_C_B95)
2931            param(1) = 0.0031d0
2932            param(2) = 0.038d0
2933            call nwxc_c_b95_d2(param,nwxc_rho_tol,ipol,nq,
2934     +                         nwxc_wghts(it),rho,gamma,tau,f)
2935          case (NWXCP_C_B97)
2936            param(1) = 2.0d0
2937            param(2) = 0.17370d+00
2938            param(3) = 0.94540d+00
2939            param(4) = 0.23487d+01
2940            param(5) = 0.74710d+00
2941            param(6) =-0.24868d+01
2942            param(7) =-0.45961d+01
2943            call nwxc_c_b97_d2(param,nwxc_rho_tol,ipol,nq,
2944     +                         nwxc_wghts(it),rho,gamma,f)
2945          case (NWXCP_C_B97_1)
2946            param(1) = 2.0d0
2947            param(2) = 0.820011d-01
2948            param(3) = 0.955689d+00
2949            param(4) = 0.271681d+01
2950            param(5) = 0.788552d+00
2951            param(6) =-0.287103d+01
2952            param(7) =-0.547869d+01
2953            call nwxc_c_b97_d2(param,nwxc_rho_tol,ipol,nq,
2954     +                         nwxc_wghts(it),rho,gamma,f)
2955          case (NWXCP_C_B97_2)
2956            param(1) = 2.0d0
2957            param(2) = 0.585808D+00
2958            param(3) = 0.999849D+00
2959            param(4) =-0.691682D+00
2960            param(5) = 0.140626D+01
2961            param(6) = 0.394796D+00
2962            param(7) =-0.744060D+01
2963            call nwxc_c_b97_d2(param,nwxc_rho_tol,ipol,nq,
2964     +                         nwxc_wghts(it),rho,gamma,f)
2965          case (NWXCP_C_B97_3)
2966            param(1)  = 4.0d0
2967            param(2)  = 5.623649D-01
2968            param(3)  = 1.133830D+00
2969            param(4)  =-1.322980D+00
2970            param(5)  =-2.811967D+00
2971            param(6)  = 6.359191D+00
2972            param(7)  = 7.431302D+00
2973            param(8)  =-7.464002D+00
2974            param(9)  =-1.969342D+00
2975            param(10) = 1.827082D+00
2976            param(11) =-1.174423D+01
2977            call nwxc_c_b97_d2(param,nwxc_rho_tol,ipol,nq,
2978     +                         nwxc_wghts(it),rho,gamma,f)
2979          case (NWXCP_C_B97_D)
2980            param(1) = 2.0d0
2981            param(2) = 0.22340d+00
2982            param(3) = 0.690410d+00
2983            param(4) =-1.562080d+00
2984            param(5) = 6.302700d00
2985            param(6) = 1.942930d+0
2986            param(7) =-14.97120d+00
2987            call nwxc_c_b97_d2(param,nwxc_rho_tol,ipol,nq,
2988     +                         nwxc_wghts(it),rho,gamma,f)
2989          case (NWXCP_C_B97_G)
2990            param(1) = 2.0d0
2991            param(2) = 0.4883d0
2992            param(3) = 0.7961d0
2993            param(4) =-2.117d0
2994            param(5) = 5.7060d0
2995            param(6) = 2.3235d0
2996            param(7) =-14.9820d0
2997            call nwxc_c_b97_d2(param,nwxc_rho_tol,ipol,nq,
2998     +                         nwxc_wghts(it),rho,gamma,f)
2999          case (NWXCP_C_B98)
3000            param(1) = 2.0d0
3001            param(2) =-0.120163d00
3002            param(3) = 0.934715d00
3003            param(4) = 2.82332d0
3004            param(5) = 1.14105d0
3005            param(6) =-2.59412d0
3006            param(7) =-5.33398d0
3007            call nwxc_c_b97_d2(param,nwxc_rho_tol,ipol,nq,
3008     +                         nwxc_wghts(it),rho,gamma,f)
3009          case (NWXCP_C_DLDF)
3010            call nwxc_c_dldf_d2(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
3011     +                       rho,gamma,tau,f)
3012          case (NWXCP_C_FT97)
3013            call nwxc_c_ft97_d2(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
3014     +                       rho,gamma,f)
3015          case (NWXCP_C_HCTH)
3016            param(1)  = 4.0d0
3017            param(2)  = 0.222601d0
3018            param(3)  = 0.729974d0
3019            param(4)  =-3.38622d-002
3020            param(5)  = 3.352870d0
3021            param(6)  =-1.25170d-002
3022            param(7)  =-11.543d0
3023            param(8)  =-0.802496d0
3024            param(9)  = 8.085640d0
3025            param(10) = 1.553960d0
3026            param(11) =-4.478570d0
3027            call nwxc_c_b97_d2(param,nwxc_rho_tol,ipol,nq,
3028     +                         nwxc_wghts(it),rho,gamma,f)
3029          case (NWXCP_C_HCTH120)
3030            param(1)  = 4.0d0
3031            param(2)  = 0.48951d0
3032            param(3)  = 0.51473d0
3033            param(4)  =-0.26070d0
3034            param(5)  = 6.92980d0
3035            param(6)  = 0.43290d0
3036            param(7)  =-24.7070d0
3037            param(8)  =-1.99250d0
3038            param(9)  = 23.1100d0
3039            param(10) = 2.48530d0
3040            param(11) =-11.3230d0
3041            call nwxc_c_b97_d2(param,nwxc_rho_tol,ipol,nq,
3042     +                         nwxc_wghts(it),rho,gamma,f)
3043          case (NWXCP_C_HCTH147)
3044            param(1)  = 4.0d0
3045            param(2)  = 0.56258d0
3046            param(3)  = 0.54235d0
3047            param(4)  =-1.71000d-002
3048            param(5)  = 7.01460d0
3049            param(6)  =-1.30640d0
3050            param(7)  =-28.3820d0
3051            param(8)  = 1.05750d0
3052            param(9)  = 35.0330d0
3053            param(10) = 0.88540d0
3054            param(11) =-20.4280d0
3055            call nwxc_c_b97_d2(param,nwxc_rho_tol,ipol,nq,
3056     +                         nwxc_wghts(it),rho,gamma,f)
3057          case (NWXCP_C_HCTH407)
3058            param(1)  = 4.0d0
3059            param(2)  = 1.18777d0
3060            param(3)  = 0.58908d0
3061            param(4)  =-2.40290d0
3062            param(5)  = 4.42370d0
3063            param(6)  = 5.61740d0
3064            param(7)  =-19.2220d0
3065            param(8)  =-9.17920d0
3066            param(9)  = 42.5720d0
3067            param(10) = 6.24800d0
3068            param(11) =-42.0050d0
3069            call nwxc_c_b97_d2(param,nwxc_rho_tol,ipol,nq,
3070     +                         nwxc_wghts(it),rho,gamma,f)
3071          case (NWXCP_C_HCTH407P)
3072            param(1)  = 4.0d0
3073            param(2)  = 0.80302d0
3074            param(3)  = 0.73604d0
3075            param(4)  =-1.04790d0
3076            param(5)  = 3.02700d0
3077            param(6)  = 4.98070d0
3078            param(7)  =-10.0750d0
3079            param(8)  =-12.8900d0
3080            param(9)  = 20.6110d0
3081            param(10) = 9.64460d0
3082            param(11) =-29.4180d0
3083            call nwxc_c_b97_d2(param,nwxc_rho_tol,ipol,nq,
3084     +                         nwxc_wghts(it),rho,gamma,f)
3085          case (NWXCP_C_HCTH_A)
3086            param(1)  = 4.0d0
3087            param(2)  = 1.36823d-002
3088            param(3)  = 0.836897d0
3089            param(4)  = 0.268920d0
3090            param(5)  = 1.720510d0
3091            param(6)  =-0.550769d0
3092            param(7)  =-2.784980d0
3093            param(8)  = 1.039470d0
3094            param(9)  =-4.575040d0
3095            param(10) = 0.000000d0
3096            param(11) = 0.000000d0
3097            call nwxc_c_b97_d2(param,nwxc_rho_tol,ipol,nq,
3098     +                         nwxc_wghts(it),rho,gamma,f)
3099          case (NWXCP_C_HCTHP14)
3100            param(1)  = 4.0d0
3101            param(2)  = 2.82414d0
3102            param(3)  = 8.21827d-002
3103            param(4)  = 3.18843d-002
3104            param(5)  = 4.56466d0
3105            param(6)  =-1.78512d0
3106            param(7)  =-13.5529d0
3107            param(8)  = 2.39795d0
3108            param(9)  = 13.3820d0
3109            param(10) =-0.876909d0
3110            param(11) =-3.174930d0
3111            call nwxc_c_b97_d2(param,nwxc_rho_tol,ipol,nq,
3112     +                         nwxc_wghts(it),rho,gamma,f)
3113          case (NWXCP_C_M05)
3114            param( 1) =   1.00000d0
3115            param( 2) =   3.78569d0
3116            param( 3) = -14.15261d0
3117            param( 4) =  -7.46589d0
3118            param( 5) =  17.94491d0
3119            param( 6) =   1.00000d0
3120            param( 7) =   3.77344d0
3121            param( 8) = -26.04463d0
3122            param( 9) =  30.69913d0
3123            param(10) =  -9.22695d0
3124            call nwxc_c_m05_d2(param,nwxc_rho_tol,ipol,nq,
3125     +           nwxc_wghts(it),rho,gamma,tau,f)
3126          case (NWXCP_C_M05_2X)
3127            param( 1) =   1.00000d0
3128            param( 2) =   1.09297d0
3129            param( 3) =  -3.79171d0
3130            param( 4) =   2.82810d0
3131            param( 5) = -10.58909d0
3132            param( 6) =   1.00000d0
3133            param( 7) =  -3.05430d0
3134            param( 8) =   7.61854d0
3135            param( 9) =   1.47665d0
3136            param(10) = -11.92365d0
3137            call nwxc_c_m05_d2(param,nwxc_rho_tol,ipol,nq,
3138     +           nwxc_wghts(it),rho,gamma,tau,f)
3139          case (NWXCP_C_M06)
3140c
3141            param( 1) =  -2.741539D+00
3142            param( 2) =  -6.720113D-01
3143            param( 3) =  -7.932688D-02
3144            param( 4) =   1.918681D-03
3145            param( 5) =  -2.032902D-03
3146            param( 6) =   0.000000D+00
3147            param( 7) =   4.905945D-01
3148            param( 8) =  -1.437348D-01
3149            param( 9) =   2.357824D-01
3150            param(10) =   1.871015D-03
3151            param(11) =  -3.788963D-03
3152            param(12) =   0.000000D+00
3153c
3154            param(13) =   3.741539D+00
3155            param(14) =   2.187098D+02
3156            param(15) =  -4.531252D+02
3157            param(16) =   2.936479D+02
3158            param(17) =  -6.287470D+01
3159            param(18) =   5.094055D-01
3160            param(19) =  -1.491085D+00
3161            param(20) =   1.723922D+01
3162            param(21) =  -3.859018D+01
3163            param(22) =   2.845044D+01
3164c
3165            call nwxc_c_m06_d2(param,nwxc_rho_tol,ipol,nq,
3166     +           nwxc_wghts(it),rho,gamma,tau,f)
3167          case (NWXCP_C_M06_HF)
3168c
3169            param( 1) =  -6.746338D-01
3170            param( 2) =  -1.534002D-01
3171            param( 3) =  -9.021521D-02
3172            param( 4) =  -1.292037D-03
3173            param( 5) =  -2.352983D-04
3174            param( 6) =   0.000000D+00
3175            param( 7) =   8.976746D-01
3176            param( 8) =  -2.345830D-01
3177            param( 9) =   2.368173D-01
3178            param(10) =  -9.913890D-04
3179            param(11) =  -1.146165D-02
3180            param(12) =   0.000000D+00
3181c
3182            param(13) =   1.674634D+00
3183            param(14) =   5.732017D+01
3184            param(15) =   5.955416D+01
3185            param(16) =  -2.311007D+02
3186            param(17) =   1.255199D+02
3187            param(18) =   1.023254D-01
3188            param(19) =  -2.453783D+00
3189            param(20) =   2.913180D+01
3190            param(21) =  -3.494358D+01
3191            param(22) =   2.315955D+01
3192c
3193            call nwxc_c_m06_d2(param,nwxc_rho_tol,ipol,nq,
3194     +           nwxc_wghts(it),rho,gamma,tau,f)
3195          case (NWXCP_C_M06_L)
3196c
3197            param( 1) =   3.957626D-01
3198            param( 2) =  -5.614546D-01
3199            param( 3) =   1.403963D-02
3200            param( 4) =   9.831442D-04
3201            param( 5) =  -3.577176D-03
3202            param( 6) =   0.000000D+00
3203            param( 7) =   4.650534D-01
3204            param( 8) =   1.617589D-01
3205            param( 9) =   1.833657D-01
3206            param(10) =   4.692100D-04
3207            param(11) =  -4.990573D-03
3208            param(12) =   0.000000D+00
3209c
3210            param(13) =   6.042374D-01
3211            param(14) =   1.776783D+02
3212            param(15) =  -2.513252D+02
3213            param(16) =   7.635173D+01
3214            param(17) =  -1.255699D+01
3215            param(18) =   5.349466D-01
3216            param(19) =   5.396620D-01
3217            param(20) =  -3.161217D+01
3218            param(21) =   5.149592D+01
3219            param(22) =  -2.919613D+01
3220c
3221            call nwxc_c_m06_d2(param,nwxc_rho_tol,ipol,nq,
3222     +           nwxc_wghts(it),rho,gamma,tau,f)
3223          case (NWXCP_C_M06_2X)
3224c
3225            param( 1) =   1.166404D-01
3226            param( 2) =  -9.120847D-02
3227            param( 3) =  -6.726189D-02
3228            param( 4) =   6.720580D-05
3229            param( 5) =   8.448011D-04
3230            param( 6) =   0.000000D+00
3231            param( 7) =   6.902145D-01
3232            param( 8) =   9.847204D-02
3233            param( 9) =   2.214797D-01
3234            param(10) =  -1.968264D-03
3235            param(11) =  -6.775479D-03
3236            param(12) =   0.000000D+00
3237c
3238            param(13) =   8.833596D-01
3239            param(14) =   3.357972D+01
3240            param(15) =  -7.043548D+01
3241            param(16) =   4.978271D+01
3242            param(17) =  -1.852891D+01
3243            param(18) =   3.097855D-01
3244            param(19) =  -5.528642D+00
3245            param(20) =   1.347420D+01
3246            param(21) =  -3.213623D+01
3247            param(22) =   2.846742D+01
3248c
3249            call nwxc_c_m06_d2(param,nwxc_rho_tol,ipol,nq,
3250     +           nwxc_wghts(it),rho,gamma,tau,f)
3251          case (NWXCP_C_M08_HX)
3252c           parameters A
3253            param(1)  =    1.0000000D+00
3254            param(2)  =   -4.0661387D-01
3255            param(3)  =   -3.3232530D+00
3256            param(4)  =    1.5540980D+00
3257            param(5)  =    4.4248033D+01
3258            param(6)  =   -8.4351930D+01
3259            param(7)  =   -1.1955581D+02
3260            param(8)  =    3.9147081D+02
3261            param(9)  =    1.8363851D+02
3262            param(10) =   -6.3268223D+02
3263            param(11) =   -1.1297403D+02
3264            param(12) =    3.3629312D+02
3265c           parameters B
3266            param(13) =    1.3812334D+00
3267            param(14) =   -2.4683806D+00
3268            param(15) =   -1.1901501D+01
3269            param(16) =   -5.4112667D+01
3270            param(17) =    1.0055846D+01
3271            param(18) =    1.4800687D+02
3272            param(19) =    1.1561420D+02
3273            param(20) =    2.5591815D+02
3274            param(21) =    2.1320772D+02
3275            param(22) =   -4.8412067D+02
3276            param(23) =   -4.3430813D+02
3277            param(24) =    5.6627964D+01
3278            call nwxc_c_m11_d2(param,nwxc_rho_tol,ipol,nq,
3279     +           nwxc_wghts(it),rho,gamma,tau,f)
3280          case (NWXCP_C_M08_SO)
3281c           parameters A
3282            param(1)  =   1.0000000D+00
3283            param(2)  =   0.0000000D+00
3284            param(3)  =  -3.9980886D+00
3285            param(4)  =   1.2982340D+01
3286            param(5)  =   1.0117507D+02
3287            param(6)  =  -8.9541984D+01
3288            param(7)  =  -3.5640242D+02
3289            param(8)  =   2.0698803D+02
3290            param(9)  =   4.6037780D+02
3291            param(10) =  -2.4510559D+02
3292            param(11) = -1.9638425D+02
3293            param(12) =  1.1881459D+02
3294c           parameters B
3295            param(13) =   1.0000000D+00
3296            param(14) =  -4.4117403D+00
3297            param(15) =  -6.4128622D+00
3298            param(16) =   4.7583635D+01
3299            param(17) =   1.8630053D+02
3300            param(18) =  -1.2800784D+02
3301            param(19) =  -5.5385258D+02
3302            param(20) =   1.3873727D+02
3303            param(21) =   4.1646537D+02
3304            param(22) =  -2.6626577D+02
3305            param(23) =   5.6676300D+01
3306            param(24) =   3.1673746D+02
3307            call nwxc_c_m11_d2(param,nwxc_rho_tol,ipol,nq,
3308     +           nwxc_wghts(it),rho,gamma,tau,f)
3309          case (NWXCP_C_M11)
3310c            parameters A
3311            param(1)  =  1.0000000D+00
3312            param(2)  =  0.0000000D+00
3313            param(3)  = -3.8933250D+00
3314            param(4)  = -2.1688455D+00
3315            param(5)  =  9.3497200D+00
3316            param(6)  = -1.9845140D+01
3317            param(7)  =  2.3455253D+00
3318            param(8)  =  7.9246513D+01
3319            param(9)  =  9.6042757D+00
3320            param(10) = -6.7856719D+01
3321            param(11) = -9.1841067D+00
3322            param(12) =  0.0000000D+00
3323c           parameters B
3324            param(13) =  7.2239798D-01
3325            param(14) =  4.3730564D-01
3326            param(15) = -1.6088809D+01
3327            param(16) = -6.5542437D+01
3328            param(17) =  3.2057230D+01
3329            param(18) =  1.8617888D+02
3330            param(19) =  2.0483468D+01
3331            param(20) = -7.0853739D+01
3332            param(21) =  4.4483915D+01
3333            param(22) = -9.4484747D+01
3334            param(23) = -1.1459868D+02
3335            param(24) =  0.0000000D+00
3336            call nwxc_c_m11_d2(param,nwxc_rho_tol,ipol,nq,
3337     +           nwxc_wghts(it),rho,gamma,tau,f)
3338          case (NWXCP_C_M11_L)
3339c           parameters A
3340            param(1)  =  1.000000D+00
3341            param(2)  =  0.000000D+00
3342            param(3)  =  2.750880D+00
3343            param(4)  = -1.562287D+01
3344            param(5)  =  9.363381D+00
3345            param(6)  =  2.141024D+01
3346            param(7)  = -1.424975D+01
3347            param(8)  = -1.134712D+01
3348            param(9)  =  1.022365D+01
3349            param(10) =  0.000000D+00
3350            param(11) =  0.000000D+00
3351            param(12) =  0.000000D+00
3352c           parameters B
3353            param(13) =  1.000000D+00
3354            param(14) = -9.082060D+00
3355            param(15) =  6.134682D+00
3356            param(16) = -1.333216D+01
3357            param(17) = -1.464115D+01
3358            param(18) =  1.713143D+01
3359            param(19) =  2.480738D+00
3360            param(20) = -1.007036D+01
3361            param(21) = -1.117521D-01
3362            param(22) =  0.000000D+00
3363            param(23) =  0.000000D+00
3364            param(24) =  0.000000D+00
3365            call nwxc_c_m11_d2(param,nwxc_rho_tol,ipol,nq,
3366     +           nwxc_wghts(it),rho,gamma,tau,f)
3367          case (NWXCP_C_MPBE)
3368            param(1) = 0.066724550603149d0
3369            call nwxc_c_mpbe_d2(param,nwxc_rho_tol,ipol,nq,
3370     +           nwxc_wghts(it),rho,gamma,f)
3371          case (NWXCP_C_OP)
3372            param(1) = 2.3670d0
3373            call nwxc_c_op_d2(nwxc_k_becke88_d2,param,nwxc_rho_tol,
3374     +           ipol,nq,nwxc_wghts(it),rho,gamma,f)
3375          case (NWXCP_C_OPT)
3376            call nwxc_c_opt_d2(nwxc_rho_tol,ipol,nq,
3377     +           nwxc_wghts(it),rho,gamma,f)
3378          case (NWXCP_C_PW6B95)
3379            param(1) = 0.00262d0
3380            param(2) = 0.03668d0
3381            call nwxc_c_b95_d2(param,nwxc_rho_tol,ipol,nq,
3382     +                      nwxc_wghts(it),rho,gamma,tau,f)
3383          case (NWXCP_C_PWB6K)
3384            param(1) = 0.00353d0
3385            param(2) = 0.04120d0
3386            call nwxc_c_b95_d2(param,nwxc_rho_tol,ipol,nq,
3387     +                      nwxc_wghts(it),rho,gamma,tau,f)
3388          case (NWXCP_C_PW91LDA)
3389            call nwxc_c_pw91lda_d2(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
3390     +                             rho,f)
3391          case (NWXCP_C_LYP)
3392            call nwxc_c_lyp_d2(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
3393     +                         rho,gamma,f)
3394          case (NWXCP_C_PZ81)
3395            call nwxc_c_perdew81_d2(nwxc_rho_tol,ipol,nq,
3396     +                              nwxc_wghts(it),rho,f)
3397          case (NWXCP_C_P86)
3398            call nwxc_c_perdew86_d2(nwxc_rho_tol,ipol,nq,
3399     +                              nwxc_wghts(it),rho,gamma,f)
3400          case (NWXCP_C_P91)
3401            call nwxc_c_p91_d2(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
3402     +                         rho,gamma,f)
3403          case (NWXCP_C_P91_VWN5)
3404            call nwxc_c_p91_vwn5_d2(nwxc_rho_tol,ipol,nq,
3405     +                              nwxc_wghts(it),rho,gamma,f,dfdr)
3406          case (NWXCP_C_PBE)
3407            param(1) = 0.066724550603149d0
3408            call nwxc_c_pbe_d2(param,nwxc_rho_tol,ipol,nq,
3409     +                         nwxc_wghts(it),rho,gamma,f)
3410          case (NWXCP_C_PBESOL)
3411            param(1) = 0.046d0
3412            call nwxc_c_pbe_d2(param,nwxc_rho_tol,ipol,nq,
3413     +                         nwxc_wghts(it),rho,gamma,f)
3414          case (NWXCP_C_PKZB)
3415            param(1) = 0.066724550603149d0
3416            call nwxc_c_pkzb99_d2(param,nwxc_rho_tol,ipol,nq,
3417     +                            nwxc_wghts(it),rho,gamma,tau,f)
3418          case (NWXCP_C_SPBE)
3419            call nwxc_c_spbe_d2(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
3420     +                          rho,gamma,f)
3421          case (NWXCP_C_SOGGA11)
3422            param(1)  =  5.00000d-01
3423            param(2)  = -4.62334D+00
3424            param(3)  =  8.00410D+00
3425            param(4)  = -130.226D+00
3426            param(5)  =  38.2685D+00
3427            param(6)  =  69.5599D+00
3428            param(7)  =  5.00000d-01
3429            param(8)  =  3.62334D+00
3430            param(9)  =  9.36393D+00
3431            param(10) =  34.5114D+00
3432            param(11) = -18.5684D+00
3433            param(12) = -0.16519D+00
3434            call nwxc_c_sogga_d2(param,nwxc_rho_tol,ipol,nq,
3435     +                           nwxc_wghts(it),rho,gamma,f)
3436          case (NWXCP_C_SOGGA11_X)
3437            param(1)  =  5.00000d-01
3438            param(2)  =  7.82439d+01
3439            param(3)  =  2.57211d+01
3440            param(4)  = -1.38830d+01
3441            param(5)  = -9.87375d+00
3442            param(6)  = -1.41357d+01
3443            param(7)  =  5.00000d-01
3444            param(8)  = -7.92439d+01
3445            param(9)  =  1.63725d+01
3446            param(10) =  2.08129d+00
3447            param(11) =  7.50769d+00
3448            param(12) = -1.01861d+01
3449            call nwxc_c_sogga_d2(param,nwxc_rho_tol,ipol,nq,
3450     +                           nwxc_wghts(it),rho,gamma,f)
3451          case (NWXCP_C_TPSS)
3452            param(1) = 0.066724550603149d0
3453            call nwxc_c_tpss03_d2(param,nwxc_rho_tol,ipol,nq,
3454     +                            nwxc_wghts(it),rho,gamma,tau,f)
3455          case (NWXCP_C_VS98)
3456            param(1)  =  7.035010d-01
3457            param(2)  =  7.694574d-03
3458            param(3)  =  5.152765d-02
3459            param(4)  =  3.394308d-05
3460            param(5)  = -1.269420d-03
3461            param(6)  =  1.296118d-03
3462            param(7)  =  3.270912d-01
3463            param(8)  = -3.228915d-02
3464            param(9)  = -2.942406d-02
3465            param(10) =  2.134222d-03
3466            param(11) = -5.451559d-03
3467            param(12) =  1.577575d-02
3468            call nwxc_c_vs98_d2(param,nwxc_rho_tol,ipol,nq,
3469     +           nwxc_wghts(it),rho,gamma,tau,f)
3470          case (NWXCP_C_VWN1)
3471            call nwxc_c_vwn1_d2(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
3472     +                          rho,f)
3473          case (NWXCP_C_VWN1_RPA)
3474            call nwxc_c_vwn1_rpa_d2(nwxc_rho_tol,ipol,nq,
3475     +                              nwxc_wghts(it),
3476     +                              rho,f)
3477          case (NWXCP_C_VWN2)
3478            call nwxc_c_vwn2_d2(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
3479     +                          rho,f)
3480          case (NWXCP_C_VWN3)
3481            call nwxc_c_vwn3_d2(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
3482     +                          rho,f)
3483          case (NWXCP_C_VWN4)
3484            call nwxc_c_vwn4_d2(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
3485     +                          rho,f)
3486          case (NWXCP_C_VWN5)
3487            call nwxc_c_vwn5_d2(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
3488     +                          rho,f)
3489          case (NWXCP_BOP)
3490            param(1) = 2.3670d0
3491            call nwxc_c_op_d2(nwxc_k_becke88_d2,param,nwxc_rho_tol,
3492     +           ipol,nq,nwxc_wghts(it),rho,gamma,f)
3493          case (NWXCP_KT1)
3494            call nwxc_xc_kt1_d2(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
3495     +                          rho,gamma,f)
3496          case (NWXCP_PBEOP)
3497            param(1) = 2.3789d0
3498            call nwxc_c_op_d2(nwxc_k_pbe96_d2,param,nwxc_rho_tol,
3499     +           ipol,nq,nwxc_wghts(it),rho,gamma,f)
3500          case (NWXCP_SOP)
3501            param(1) = 2.5654d0
3502            call nwxc_c_op_d2(nwxc_k_dirac_d2,param,nwxc_rho_tol,
3503     +           ipol,nq,nwxc_wghts(it),rho,gamma,f)
3504          case default
3505            if (nwxc_oroot) then
3506              write(*,*)"nwxc_eval_df2: invalid functional",
3507     +                  nwxc_ids(it)
3508            endif
3509            call nwxc_printP()
3510            call errquit("nwxc_eval_df2: invalid functional",
3511     +                   nwxc_ids(it),0)
3512        end select
3513      enddo
3514C
3515      end
3516C>
3517C> @}
3518C>
3519C> \ingroup nwad_api
3520C> @{
3521C>
3522C> \brief The functional, 1st, 2nd, and 3rd order partial derivative
3523C> evaluation
3524C>
3525      subroutine nwxc_eval_df3(ipol,nq,rho,gamma,tau,f,
3526     +           dfdr,dfdr2,dfdr3,dfdg,dfdg2,dfdg3,dfdt,dfdt2,dfdt3)
3527      implicit none
3528#include "errquit.fh"
3529#include "nwxcP.fh"
3530#include "nwxc_param.fh"
3531      integer ipol !< [Input] The number of spin channels
3532      integer nq   !< [Input] The number of points
3533C
3534      double precision rho(nq,ipol)     !< [Input] Density
3535      double precision gamma(nq,ipol+1) !< [Input] |Density gradient|^2
3536      double precision tau(nq,ipol)     !< [Input] Kinetic energy
3537                                        !< density
3538C
3539      double precision f(nq)           !< [Output] Energy
3540      double precision dfdr(nq,ipol)   !< [Output] Derivative wrt rho
3541      double precision dfdg(nq,ipol+1) !< [Output] Derivative wrt gamma
3542      double precision dfdt(nq,ipol)   !< [Output] Derivative wrt tau
3543      double precision dfdr2(nq,NCOL_AMAT2) !< [Output] 2nd derivative wrt rho
3544      double precision dfdg2(nq,NCOL_CMAT2) !< [Output] 2nd derivative wrt gamma
3545      double precision dfdt2(nq,NCOL_MMAT2) !< [Output] 2nd derivative wrt tau
3546      double precision dfdr3(nq,NCOL_AMAT3) !< [Output] 3rd derivative wrt rho
3547      double precision dfdg3(nq,NCOL_CMAT3) !< [Output] 3rd derivative wrt gamma
3548      double precision dfdt3(nq,NCOL_MMAT3) !< [Output] 3rd derivative wrt tau
3549      if (nwxc_eval_method.eq.NWXCP_EVAL_AUTODF) then
3550        call nwxca_eval_df3(ipol,nq,rho,gamma,tau,f,
3551     +       dfdr,dfdr2,dfdr3,dfdg,dfdg2,dfdg3,dfdt,dfdt2,dfdt3)
3552      else if (nwxc_eval_method.eq.NWXCP_EVAL_MAXIMA) then
3553        call nwxcm_eval_df3(ipol,nq,rho,gamma,tau,f,
3554     +       dfdr,dfdr2,dfdr3,dfdg,dfdg2,dfdg3,dfdt,dfdt2,dfdt3)
3555      else
3556        call errquit("nwxc_eval_df3: unknown evaluator",
3557     +               nwxc_eval_method,UERR)
3558      endif
3559
3560      end
3561C>
3562C> @}
3563C>
3564C> \ingroup nwad_priv
3565C> @{
3566C>
3567C> \brief The functional, 1st, 2nd, and 3rd order partial derivative
3568C> evaluation with AD
3569C>
3570C> In actual fact this routine only sets up the memory and then calls
3571C> the driver routine to drive the actual functional evaluation. The
3572C> lack of a Fortran90 typecast drives this code structure.
3573C>
3574      subroutine nwxca_eval_df3(ipol,nq,rho,gamma,tau,f,
3575     +           dfdr,dfdr2,dfdr3,dfdg,dfdg2,dfdg3,dfdt,dfdt2,dfdt3)
3576      use nwad3
3577      implicit none
3578#include "errquit.fh"
3579#include "mafdecls.fh"
3580#include "nwxc_param.fh"
3581      integer ipol !< [Input] The number of spin channels
3582      integer nq   !< [Input] The number of points
3583C
3584      double precision rho(nq,ipol)     !< [Input] Density
3585      double precision gamma(nq,ipol+1) !< [Input] |Density gradient|^2
3586      double precision tau(nq,ipol)     !< [Input] Kinetic energy
3587                                        !< density
3588C
3589      double precision f(nq)           !< [Output] Energy
3590      double precision dfdr(nq,ipol)   !< [Output] Derivative wrt rho
3591      double precision dfdg(nq,ipol+1) !< [Output] Derivative wrt gamma
3592      double precision dfdt(nq,ipol)   !< [Output] Derivative wrt tau
3593      double precision dfdr2(nq,NCOL_AMAT2) !< [Output] 2nd derivative wrt rho
3594      double precision dfdg2(nq,NCOL_CMAT2) !< [Output] 2nd derivative wrt gamma
3595      double precision dfdt2(nq,NCOL_MMAT2) !< [Output] 2nd derivative wrt tau
3596      double precision dfdr3(nq,NCOL_AMAT3) !< [Output] 3rd derivative wrt rho
3597      double precision dfdg3(nq,NCOL_CMAT3) !< [Output] 3rd derivative wrt gamma
3598      double precision dfdt3(nq,NCOL_MMAT3) !< [Output] 3rd derivative wrt tau
3599c
3600      type(nwad_dble) :: memory_test_nwad(2)
3601      double precision   memory_test_dble(2)
3602      integer length
3603      integer l_rho, k_rho !< Index for density
3604      integer l_gam, k_gam !< Index for gradient
3605      integer l_tau, k_tau !< Index for kinetic energy density
3606      integer l_fun, k_fun !< Index for functional
3607      integer l_scr, k_scr !< Index for functional
3608      integer nvar         !< The number of variables in the functional
3609                           !< LDA: nvar=ipol, GGA: nvar=2*ipol+1,
3610                           !< MGGA: nvar=3*ipol+1
3611      integer ndrv         !< The number of partial derivatives
3612      integer ipl          !< Hack version of ipol
3613C
3614      logical nwxc_is_gga  !< Is the functional a GGA
3615      logical nwxc_is_mgga !< Is the functional a meta-GGA
3616c
3617c     Work out nvar for this functional
3618c
3619      ipl = 2
3620      nvar = ipol
3621      if (nwxc_is_gga().or.nwxc_is_mgga()) then
3622        nvar = nvar + ipol+1
3623        if (nwxc_is_mgga()) then
3624          nvar = nvar + ipol
3625        endif
3626      endif
3627      ndrv = nvar*(nvar+1)*(nvar+2)/6
3628c
3629c     Work out how many double precision floating point words are needed
3630c     to represent a single nwad_dble
3631c
3632      length = (loc(memory_test_dble(2))-loc(memory_test_dble(1)))
3633      length = (loc(memory_test_nwad(2))-loc(memory_test_nwad(1))
3634     +          +length-1)/length
3635      if(.not.ma_push_get(mt_dbl,length*nq*ipl,"nwad rho",l_rho,k_rho))
3636     +  call errquit("nwxca_eval_df3: cannot allocate nwad rho",
3637     +    ma_sizeof(mt_dbl,length*nq*ipl,mt_byte),MA_ERR)
3638      if(.not.ma_push_get(mt_dbl,length*nq*(ipl+1),"nwad gamma",
3639     +                    l_gam,k_gam))
3640     +  call errquit("nwxca_eval_df3: cannot allocate nwad gamma",
3641     +    ma_sizeof(mt_dbl,length*nq*(ipl+1),mt_byte),MA_ERR)
3642      if(.not.ma_push_get(mt_dbl,length*nq*ipl,"nwad tau",l_tau,k_tau))
3643     +  call errquit("nwxca_eval_df3: cannot allocate nwad tau",
3644     +    ma_sizeof(mt_dbl,length*nq*ipl,mt_byte),MA_ERR)
3645      if(.not.ma_push_get(mt_dbl,length*nq*ndrv,"nwad fun",l_fun,k_fun))
3646     +  call errquit("nwxca_eval_df3: cannot allocate nwad fun",
3647     +    ma_sizeof(mt_dbl,length*nq*ndrv,mt_byte),MA_ERR)
3648c
3649      call nwxc_eval_df3_driver(ipol,nq,rho,gamma,tau,dbl_mb(k_rho),
3650     +     dbl_mb(k_gam),dbl_mb(k_tau),dbl_mb(k_fun),
3651     +     nvar,ndrv,
3652     +     f,dfdr,dfdr2,dfdr3,dfdg,dfdg2,dfdg3,dfdt,dfdt2,dfdt3)
3653c
3654      if(.not.ma_pop_stack(l_fun)) call errquit(
3655     +  "nwxca_eval_df3: cannot deallocate nwad fun",0,MA_ERR)
3656      if(.not.ma_pop_stack(l_tau)) call errquit(
3657     +  "nwxca_eval_df3: cannot deallocate nwad tau",0,MA_ERR)
3658      if(.not.ma_pop_stack(l_gam)) call errquit(
3659     +  "nwxca_eval_df3: cannot deallocate nwad gam",0,MA_ERR)
3660      if(.not.ma_pop_stack(l_rho)) call errquit(
3661     +  "nwxca_eval_df3: cannot deallocate nwad rho",0,MA_ERR)
3662      end
3663C>
3664C> \brief Driver routine for the functional, 1st, 2nd and 3rd derivative
3665C> evaluation
3666C>
3667C> This driver routine initializes the active variables and invokes the
3668C> functional evaluation. Afterwards the results are unpacked and stored
3669C> into the output arrays. The handling of the closed shell case follows
3670C> the same approach as outlined with `nwxc_eval_df2_driver`.
3671C>
3672      subroutine nwxc_eval_df3_driver(ipol,nq,rho,gamma,tau,
3673     +           nwad_rho,nwad_gam,nwad_tau,nwad_f,nvar,ndrv,
3674     +           f,dfdr,dfdr2,dfdr3,dfdg,dfdg2,dfdg3,dfdt,dfdt2,dfdt3)
3675      use nwad3
3676      implicit none
3677#include "errquit.fh"
3678#include "nwxc_param.fh"
3679      integer ipol !< [Input] The number of spin channels
3680      integer nq   !< [Input] The number of points
3681      integer nvar !< [Input] The number of independent variables
3682      integer ndrv !< [Input] The number of 2nd order partial derivatives
3683C
3684      double precision rho(nq,ipol) !< [Input] Density
3685      double precision gamma(nq,3)  !< [Input] |Density gradient|^2
3686      double precision tau(nq,ipol) !< [Input] Kinetic energy
3687                                    !< density
3688C
3689      double precision f(nq)           !< [Output] Energy
3690      double precision dfdr(nq,ipol)   !< [Output] Derivative wrt rho
3691      double precision dfdg(nq,ipol+1) !< [Output] Derivative wrt gamma
3692      double precision dfdt(nq,ipol)   !< [Output] Derivative wrt tau
3693      double precision dfdr2(nq,NCOL_AMAT2) !< [Output] 2nd derivative wrt rho
3694      double precision dfdg2(nq,NCOL_CMAT2) !< [Output] 2nd derivative wrt gamma
3695      double precision dfdt2(nq,NCOL_MMAT2) !< [Output] 2nd derivative wrt tau
3696      double precision dfdr3(nq,NCOL_AMAT3) !< [Output] 3rd derivative wrt rho
3697      double precision dfdg3(nq,NCOL_CMAT3) !< [Output] 3rd derivative wrt gamma
3698      double precision dfdt3(nq,NCOL_MMAT3) !< [Output] 3rd derivative wrt tau
3699c
3700      type(nwad_dble) :: nwad_rho(nq,2)
3701      type(nwad_dble) :: nwad_gam(nq,3)
3702      type(nwad_dble) :: nwad_tau(nq,2)
3703      type(nwad_dble) :: nwad_f(nq)
3704C
3705      logical nwxc_is_gga  !< Is the functional a GGA
3706      logical nwxc_is_mgga !< Is the functional a meta-GGA
3707c
3708c     integer ir_t, ig_tt, it_t
3709c     integer ir_a, ir_b, ig_aa, ig_ab, ig_bb, it_a, it_b
3710c     integer iq, ip, id, ir, it
3711c     integer ip2, ir2, ipr, id2
3712c     integer ip3, ir3, it3, ip2r, ip2t, ipr2, ir2t, ipt2, irt2, iprt
3713      integer iq
3714      integer ix1, ix2, ix3
3715      integer iv1, iv2, iv3
3716c
3717      double precision val
3718c
3719c     Scaling factors to convert
3720c     - df/drho,
3721c     - df/dgamma and
3722c     - df/dtau
3723c     to the quantities NWChem expects, i.e.
3724c     - df/drhoa
3725c     - df/dgammaaa+1/2*df/dgammaab
3726c     - df/dta
3727c
3728c     For the second derivatives
3729c     - d2f/drho2
3730c     - d2f/drhodgamma
3731c     - d2f/dgamma2
3732c     - d2f/drhodtau
3733c     - d2f/dgammadtau
3734c     - d2f/dtau2
3735c     to the quantities NWChems expects, i.e.
3736c     - d2f/drhoa2+d2f/drhoadrhob
3737c     - d2f/drhoadgammaaa+d2f/drhoadgammaab+d2f/drhoadgammabb
3738c     - d2f/dgammaaa2+d2f/dgammaaadgammaab+d2f/dgammaaadgammabb
3739c       +d2f/dgammaab2
3740c     - d2f/drhoadtaua+d2f/drhoadtaub
3741c     - d2f/dgammaaadtaua+d2f/dgammaabdtaua+d2f/dgammabbdtaua
3742c     - d2f/dtaua2+d2f/dtauadtaub
3743c
3744c     For the third derivatives
3745c     - d3f/drho3
3746c     - d3f/drho2dgamma
3747c     - d3f/drhodgamma2
3748c     - d3f/dgamma3
3749c     - d3f/drho2dtau
3750c     - d3f/drhodtau2
3751c     - d3f/dtau3
3752c     to the quantities NWChems expects, i.e.
3753c     - d3f/drhoa3+3*d3f/drhoa2drhob
3754c     - d3f/drhoa2dgammaaa+d3f/drhoa2dgammaab+d3f/drhoa2dgammabb
3755c       +d3f/drhoadrhobdgammaaa+d3f/drhoadrhobdgammaab
3756c       +d3f/drhoadrhobdgammabb
3757c     - d3f/drhoadgammaaa2+2*d3f/drhoadgammaaadgammaab
3758c       +2*d3f/drhoadgammaaadgammabb+d3f/drhoadgammaab2
3759c       +2*d3f/drhoadgammaabdgammabb+d3f/drhoadgammabb2
3760c     - d3f/dgammaaa3+3/2*d3f/dgammaaa2dgammaab
3761c       +3/2*d3f/dgammaaa2dgammabb+3/2*d3f/dgammaaadgammaab2
3762c       +3*d3f/dgammaaadgammaabdgammabb+3/2*d3f/dgammaaadgammabb2
3763c     - d3f/drhoa2dtaua+d3f/drhoa2dtaub+2*d3f/drhoadrhobdtaua
3764c     - d3f/drhoadtaua2+d3f/drhoadtaub2+2*d3f/drhoadtauadtaub
3765c     - d3f/dtaua3+3*d3f/dtaua2dtaub
3766c
3767      double precision sfac_ra  !< the closed shell RA scaling factor
3768      double precision sfac_gaa !< the closed shell GAA scaling factor
3769      double precision sfac_ta  !< the closed shell TA scaling factor
3770      parameter(sfac_ra  = 1.0d0)
3771      parameter(sfac_gaa = 2.0d0)
3772      parameter(sfac_ta  = 1.0d0)
3773      double precision sfac_rara   !< a closed shell scaling factor
3774      double precision sfac_ragaa  !< a closed shell scaling factor
3775      double precision sfac_gaagaa !< a closed shell scaling factor
3776      double precision sfac_rata   !< a closed shell scaling factor
3777      double precision sfac_gaata  !< a closed shell scaling factor
3778      double precision sfac_tata   !< a closed shell scaling factor
3779      parameter(sfac_rara   = 2.0d0)
3780      parameter(sfac_ragaa  = 4.0d0)
3781      parameter(sfac_gaagaa = 8.0d0)
3782      parameter(sfac_rata   = 2.0d0)
3783      parameter(sfac_gaata  = 4.0d0)
3784      parameter(sfac_tata   = 2.0d0)
3785      double precision sfac_rarara    !< a closed shell scaling factor
3786      double precision sfac_raragaa   !< a closed shell scaling factor
3787      double precision sfac_ragaagaa  !< a closed shell scaling factor
3788      double precision sfac_gaagaagaa !< a closed shell scaling factor
3789      parameter(sfac_rarara    =  4.0d0)
3790      parameter(sfac_raragaa   =  8.0d0)
3791      parameter(sfac_ragaagaa  = 16.0d0)
3792      parameter(sfac_gaagaagaa = 32.0d0)
3793      double precision sfac_rarata    !< a closed shell scaling factor
3794      double precision sfac_ratata    !< a closed shell scaling factor
3795      double precision sfac_tatata    !< a closed shell scaling factor
3796      parameter(sfac_rarata    =  4.0d0)
3797      parameter(sfac_ratata    =  4.0d0)
3798      parameter(sfac_tatata    =  4.0d0)
3799c
3800c     The following constants are tentative (M06 in particular seems to
3801c     cause problems)
3802c
3803      double precision sfac_ragaata    !< a closed shell scaling factor
3804      double precision sfac_gaagaata   !< a closed shell scaling factor
3805      double precision sfac_gaatata    !< a closed shell scaling factor
3806      parameter(sfac_ragaata    =  8.0d0)
3807      parameter(sfac_gaagaata   = 16.0d0)
3808      parameter(sfac_gaatata    =  8.0d0)
3809c
3810      if (ipol.eq.1) then
3811        do iq = 1, nq
3812c         nwad_rho(iq,R_T) = set_rho_t(rho(iq,R_T))
3813          nwad_rho(iq,R_A) = set_rho_a(0.5d0*rho(iq,R_T))
3814          nwad_rho(iq,R_B) = set_rho_b(0.5d0*rho(iq,R_T))
3815        enddo
3816      else  ! ipol.eq.1
3817        do iq = 1, nq
3818          nwad_rho(iq,R_A) = set_rho_a(rho(iq,R_A))
3819        enddo
3820        do iq = 1, nq
3821          nwad_rho(iq,R_B) = set_rho_b(rho(iq,R_B))
3822        enddo
3823      endif ! ipol.eq.1
3824      if (nwxc_is_gga().or.nwxc_is_mgga()) then
3825        if (ipol.eq.1) then
3826          do iq = 1, nq
3827c           nwad_gam(iq,G_TT) = set_gamma_tt(gamma(iq,G_TT))
3828            nwad_gam(iq,G_AA) = set_gamma_aa(0.5d0*gamma(iq,G_TT))
3829            nwad_gam(iq,G_AB) = set_gamma_ab(0.5d0*gamma(iq,G_TT))
3830            nwad_gam(iq,G_BB) = set_gamma_bb(0.5d0*gamma(iq,G_TT))
3831          enddo
3832        else  ! ipol.eq.1
3833          do iq = 1, nq
3834            nwad_gam(iq,G_AA) = set_gamma_aa(gamma(iq,G_AA))
3835          enddo
3836          do iq = 1, nq
3837            nwad_gam(iq,G_AB) = set_gamma_ab(gamma(iq,G_AB))
3838          enddo
3839          do iq = 1, nq
3840            nwad_gam(iq,G_BB) = set_gamma_bb(gamma(iq,G_BB))
3841          enddo
3842        endif ! ipol.eq.1
3843      endif
3844      if (nwxc_is_mgga()) then
3845        if (ipol.eq.1) then
3846          do iq = 1, nq
3847c           nwad_tau(iq,T_T) = set_tau_t(tau(iq,T_T))
3848            nwad_tau(iq,T_A) = set_tau_a(0.5d0*tau(iq,T_T))
3849            nwad_tau(iq,T_B) = set_tau_b(0.5d0*tau(iq,T_T))
3850          enddo
3851        else  ! ipol.eq.1
3852          do iq = 1, nq
3853            nwad_tau(iq,T_A) = set_tau_a(tau(iq,T_A))
3854          enddo
3855          do iq = 1, nq
3856            nwad_tau(iq,T_B) = set_tau_b(tau(iq,T_B))
3857          enddo
3858        endif ! ipol.eq.1
3859      endif
3860c
3861      call nwxc_eval_df3_doit(2,nq,nwad_rho,nwad_gam,
3862     +     nwad_tau,nwad_f,dfdr,dfdg,dfdt)
3863c
3864c     Now unpack the results
3865c
3866      if (.false..and.ipol.eq.1) then
3867c
3868c       Closed shell case -> use splitting factors
3869c
3870        do iq = 1, nq
3871          f(iq) = get_val(nwad_f(iq))
3872          nvar = get_nvar(nwad_f(iq))
3873          do ix1 = 1, nvar
3874            call get_d1(nwad_f(iq),ix1,val,iv1)
3875            select case (iv1)
3876              case (1)
3877                dfdr(iq,D1_RA) = val*sfac_ra
3878              case (3)
3879                dfdg(iq,D1_GAA) = val*sfac_gaa
3880                dfdg(iq,D1_GAB) = 0.0d0
3881              case (6)
3882                dfdt(iq,D1_TA) = val*sfac_ta
3883              case default
3884                call errquit("nwxc_df3_driver: illegal variable",
3885     +                       iv1,UERR)
3886            end select
3887            do ix2 = 1, ix1
3888              call get_d2(nwad_f(iq),ix1,ix2,val,iv1,iv2)
3889              select case (iv1)
3890                case (1)
3891                  select case (iv2)
3892                    case (1)
3893                      dfdr2(iq,D2_RA_RA) = val*sfac_rara
3894                      dfdr2(iq,D2_RA_RB) = 0.0d0
3895                  end select
3896                case (3)
3897                  select case (iv2)
3898                    case (1)
3899                      dfdg2(iq,D2_RA_GAA) = val*sfac_ragaa
3900                      dfdg2(iq,D2_RA_GAB) = 0.0d0
3901                      dfdg2(iq,D2_RA_GBB) = 0.0d0
3902                    case (3)
3903                      dfdg2(iq,D2_GAA_GAA) = val*sfac_gaagaa
3904                      dfdg2(iq,D2_GAA_GAB) = 0.0d0
3905                      dfdg2(iq,D2_GAA_GBB) = 0.0d0
3906                      dfdg2(iq,D2_GAB_GAB) = 0.0d0
3907                  end select
3908                case (6)
3909                  select case (iv2)
3910                    case (1)
3911                      dfdt2(iq,D2_RA_TA)  = val*sfac_rata
3912                      dfdt2(iq,D2_RA_TB)  = 0.0d0
3913                    case (3)
3914                      dfdt2(iq,D2_GAA_TA) = val*sfac_gaata
3915                      dfdt2(iq,D2_GAB_TA) = 0.0d0
3916                      dfdt2(iq,D2_GBB_TA) = 0.0d0
3917                    case (6)
3918                      dfdt2(iq,D2_TA_TA)  = val*sfac_tata
3919                      dfdt2(iq,D2_TA_TB)  = 0.0d0
3920                  end select
3921              end select
3922              do ix3 = 1, ix2
3923                call get_d3(nwad_f(iq),ix1,ix2,ix3,val,iv1,iv2,iv3)
3924                select case (iv1)
3925                  case (1)
3926                    select case (iv2)
3927                      case (1)
3928                        select case (iv3)
3929                          case (1)
3930                            dfdr3(iq,D3_RA_RA_RA) = val*sfac_rarara
3931                            dfdr3(iq,D3_RA_RA_RB) = 0.0d0
3932                        end select
3933                    end select
3934                  case (3)
3935                    select case (iv2)
3936                      case (1)
3937                        select case (iv3)
3938                          case (1)
3939                            dfdg3(iq,D3_RA_RA_GAA) = val*sfac_raragaa
3940                            dfdg3(iq,D3_RA_RA_GAB) = 0.0d0
3941                            dfdg3(iq,D3_RA_RA_GBB) = 0.0d0
3942                            dfdg3(iq,D3_RA_RB_GAA) = 0.0d0
3943                            dfdg3(iq,D3_RA_RB_GAB) = 0.0d0
3944                        end select
3945                      case (3)
3946                        select case (iv3)
3947                          case (1)
3948                            dfdg3(iq,D3_RA_GAA_GAA) = val*sfac_ragaagaa
3949                            dfdg3(iq,D3_RA_GAA_GAB) = 0.0d0
3950                            dfdg3(iq,D3_RA_GAA_GBB) = 0.0d0
3951                            dfdg3(iq,D3_RA_GAB_GAB) = 0.0d0
3952                            dfdg3(iq,D3_RA_GAB_GBB) = 0.0d0
3953                            dfdg3(iq,D3_RA_GBB_GBB) = 0.0d0
3954                          case (3)
3955                            dfdg3(iq,D3_GAA_GAA_GAA)
3956     +                           = val*sfac_gaagaagaa
3957                            dfdg3(iq,D3_GAA_GAA_GAB) = 0.0d0
3958                            dfdg3(iq,D3_GAA_GAA_GBB) = 0.0d0
3959                            dfdg3(iq,D3_GAA_GAB_GAB) = 0.0d0
3960                            dfdg3(iq,D3_GAA_GAB_GBB) = 0.0d0
3961                            dfdg3(iq,D3_GAB_GAB_GAB) = 0.0d0
3962                        end select
3963                    end select
3964                  case (6)
3965c                   These scale factors need more work as it requires
3966c                   meta-GGAs that have non-zero high order derivatives.
3967c                   call errquit("df3_driver: 3rd scale factors not "
3968c    +                     //"done yet",0,CAPMIS_ERR)
3969                    select case (iv2)
3970                      case (1)
3971                        select case (iv3)
3972                          case (1)
3973                            dfdt3(iq,D3_RA_RA_TA) = val*sfac_rarata
3974                            dfdt3(iq,D3_RA_RA_TB) = 0.0d0
3975                            dfdt3(iq,D3_RA_RB_TA) = 0.0d0
3976                        end select
3977                      case (3)
3978                        select case (iv3)
3979                          case (1)
3980                            dfdt3(iq,D3_RA_GAA_TA) = val*sfac_ragaata
3981                            dfdt3(iq,D3_RA_GAA_TB) = 0.0d0
3982                            dfdt3(iq,D3_RA_GAB_TA) = 0.0d0
3983                            dfdt3(iq,D3_RA_GAB_TB) = 0.0d0
3984                            dfdt3(iq,D3_RA_GBB_TA) = 0.0d0
3985                            dfdt3(iq,D3_RA_GBB_TB) = 0.0d0
3986                          case (3)
3987                            dfdt3(iq,D3_GAA_GAA_TA) = val*sfac_gaagaata
3988                            dfdt3(iq,D3_GAA_GAB_TA) = 0.0d0
3989                            dfdt3(iq,D3_GAA_GBB_TA) = 0.0d0
3990                            dfdt3(iq,D3_GAB_GAB_TA) = 0.0d0
3991                        end select
3992                      case (6)
3993                        select case (iv3)
3994                          case (1)
3995                            dfdt3(iq,D3_RA_TA_TA) = val*sfac_ratata
3996                            dfdt3(iq,D3_RA_TA_TB) = 0.0d0
3997                            dfdt3(iq,D3_RA_TB_TB) = 0.0d0
3998                          case (3)
3999                            dfdt3(iq,D3_GAA_TA_TA) = val*sfac_gaatata
4000                            dfdt3(iq,D3_GAA_TA_TB) = 0.0d0
4001                            dfdt3(iq,D3_GAB_TA_TA) = 0.0d0
4002                            dfdt3(iq,D3_GAB_TA_TB) = 0.0d0
4003                            dfdt3(iq,D3_GBB_TA_TA) = 0.0d0
4004                            dfdt3(iq,D3_GBB_TA_TB) = 0.0d0
4005                          case (6)
4006                            dfdt3(iq,D3_TA_TA_TA) = val*sfac_tatata
4007                            dfdt3(iq,D3_TA_TA_TB) = 0.0d0
4008                        end select
4009                    end select
4010                end select
4011              enddo
4012            enddo
4013          enddo
4014        enddo
4015c
4016      else
4017c
4018c       Unrestricted open shell case -> plain unpacking
4019c
4020        do iq = 1, nq
4021          f(iq) = get_val(nwad_f(iq))
4022          nvar = get_nvar(nwad_f(iq))
4023          do ix1 = 1, nvar
4024            call get_d1(nwad_f(iq),ix1,val,iv1)
4025            select case (iv1)
4026              case (1)
4027                dfdr(iq,D1_RA) = val
4028              case (2)
4029                dfdr(iq,D1_RB) = val
4030              case (3)
4031                dfdg(iq,D1_GAA) = val
4032              case (4)
4033                dfdg(iq,D1_GAB) = val
4034              case (5)
4035                dfdg(iq,D1_GBB) = val
4036              case (6)
4037                dfdt(iq,D1_TA) = val
4038              case (7)
4039                dfdt(iq,D1_TB) = val
4040              case default
4041                call errquit("nwxc_df3_driver: illegal variable",
4042     +                       iv1,UERR)
4043            end select
4044            do ix2 = 1, ix1
4045              call get_d2(nwad_f(iq),ix1,ix2,val,iv1,iv2)
4046              select case (iv1)
4047                case (1)
4048                  select case (iv2)
4049                    case (1)
4050                      dfdr2(iq,D2_RA_RA) = val
4051                  end select
4052                case (2)
4053                  select case (iv2)
4054                    case (1)
4055                      dfdr2(iq,D2_RA_RB) = val
4056                    case (2)
4057                      dfdr2(iq,D2_RB_RB) = val
4058                  end select
4059                case (3)
4060                  select case (iv2)
4061                    case (1)
4062                      dfdg2(iq,D2_RA_GAA) = val
4063                    case (2)
4064                      dfdg2(iq,D2_RB_GAA) = val
4065                    case (3)
4066                      dfdg2(iq,D2_GAA_GAA) = val
4067                  end select
4068                case (4)
4069                  select case (iv2)
4070                    case (1)
4071                      dfdg2(iq,D2_RA_GAB) = val
4072                    case (2)
4073                      dfdg2(iq,D2_RB_GAB) = val
4074                    case (3)
4075                      dfdg2(iq,D2_GAA_GAB) = val
4076                    case (4)
4077                      dfdg2(iq,D2_GAB_GAB) = val
4078                  end select
4079                case (5)
4080                  select case (iv2)
4081                    case (1)
4082                      dfdg2(iq,D2_RA_GBB) = val
4083                    case (2)
4084                      dfdg2(iq,D2_RB_GBB) = val
4085                    case (3)
4086                      dfdg2(iq,D2_GAA_GBB) = val
4087                    case (4)
4088                      dfdg2(iq,D2_GAB_GBB) = val
4089                    case (5)
4090                      dfdg2(iq,D2_GBB_GBB) = val
4091                  end select
4092                case (6)
4093                  select case (iv2)
4094                    case (1)
4095                      dfdt2(iq,D2_RA_TA) = val
4096                    case (2)
4097                      dfdt2(iq,D2_RB_TA) = val
4098                    case (3)
4099                      dfdt2(iq,D2_GAA_TA) = val
4100                    case (4)
4101                      dfdt2(iq,D2_GAB_TA) = val
4102                    case (5)
4103                      dfdt2(iq,D2_GBB_TA) = val
4104                    case (6)
4105                      dfdt2(iq,D2_TA_TA) = val
4106                  end select
4107                case (7)
4108                  select case (iv2)
4109                    case (1)
4110                      dfdt2(iq,D2_RA_TB) = val
4111                    case (2)
4112                      dfdt2(iq,D2_RB_TB) = val
4113                    case (3)
4114                      dfdt2(iq,D2_GAA_TB) = val
4115                    case (4)
4116                      dfdt2(iq,D2_GAB_TB) = val
4117                    case (5)
4118                      dfdt2(iq,D2_GBB_TB) = val
4119                    case (6)
4120                      dfdt2(iq,D2_TA_TB) = val
4121                    case (7)
4122                      dfdt2(iq,D2_TB_TB) = val
4123                  end select
4124              end select
4125              do ix3 = 1, ix2
4126                call get_d3(nwad_f(iq),ix1,ix2,ix3,val,iv1,iv2,iv3)
4127                select case (iv1)
4128                  case (1)
4129                    select case (iv2)
4130                      case (1)
4131                        select case (iv3)
4132                          case (1)
4133                            dfdr3(iq,D3_RA_RA_RA) = val
4134                        end select
4135                    end select
4136                  case (2)
4137                    select case (iv2)
4138                      case (1)
4139                        select case (iv3)
4140                          case (1)
4141                            dfdr3(iq,D3_RA_RA_RB) = val
4142                        end select
4143                      case (2)
4144                        select case (iv3)
4145                          case (1)
4146                            dfdr3(iq,D3_RA_RB_RB) = val
4147                          case (2)
4148                            dfdr3(iq,D3_RB_RB_RB) = val
4149                        end select
4150                    end select
4151                  case (3)
4152                    select case (iv2)
4153                      case (1)
4154                        select case (iv3)
4155                          case (1)
4156                            dfdg3(iq,D3_RA_RA_GAA) = val
4157                        end select
4158                      case (2)
4159                        select case (iv3)
4160                          case (1)
4161                            dfdg3(iq,D3_RA_RB_GAA) = val
4162                          case (2)
4163                            dfdg3(iq,D3_RB_RB_GAA) = val
4164                        end select
4165                      case (3)
4166                        select case (iv3)
4167                          case (1)
4168                            dfdg3(iq,D3_RA_GAA_GAA) = val
4169                          case (2)
4170                            dfdg3(iq,D3_RB_GAA_GAA) = val
4171                          case (3)
4172                            dfdg3(iq,D3_GAA_GAA_GAA) = val
4173                        end select
4174                    end select
4175                  case (4)
4176                    select case (iv2)
4177                      case (1)
4178                        select case (iv3)
4179                          case (1)
4180                            dfdg3(iq,D3_RA_RA_GAB) = val
4181                        end select
4182                      case (2)
4183                        select case (iv3)
4184                          case (1)
4185                            dfdg3(iq,D3_RA_RB_GAB) = val
4186                          case (2)
4187                            dfdg3(iq,D3_RB_RB_GAB) = val
4188                        end select
4189                      case (3)
4190                        select case (iv3)
4191                          case (1)
4192                            dfdg3(iq,D3_RA_GAA_GAB) = val
4193                          case (2)
4194                            dfdg3(iq,D3_RB_GAA_GAB) = val
4195                          case (3)
4196                            dfdg3(iq,D3_GAA_GAA_GAB) = val
4197                        end select
4198                      case (4)
4199                        select case (iv3)
4200                          case (1)
4201                            dfdg3(iq,D3_RA_GAB_GAB) = val
4202                          case (2)
4203                            dfdg3(iq,D3_RB_GAB_GAB) = val
4204                          case (3)
4205                            dfdg3(iq,D3_GAA_GAB_GAB) = val
4206                          case (4)
4207                            dfdg3(iq,D3_GAB_GAB_GAB) = val
4208                        end select
4209                    end select
4210                  case (5)
4211                    select case (iv2)
4212                      case (1)
4213                        select case (iv3)
4214                          case (1)
4215                            dfdg3(iq,D3_RA_RA_GBB) = val
4216                        end select
4217                      case (2)
4218                        select case (iv3)
4219                          case (1)
4220                            dfdg3(iq,D3_RA_RB_GBB) = val
4221                          case (2)
4222                            dfdg3(iq,D3_RB_RB_GBB) = val
4223                        end select
4224                      case (3)
4225                        select case (iv3)
4226                          case (1)
4227                            dfdg3(iq,D3_RA_GAA_GBB) = val
4228                          case (2)
4229                            dfdg3(iq,D3_RB_GAA_GBB) = val
4230                          case (3)
4231                            dfdg3(iq,D3_GAA_GAA_GBB) = val
4232                        end select
4233                      case (4)
4234                        select case (iv3)
4235                          case (1)
4236                            dfdg3(iq,D3_RA_GAB_GBB) = val
4237                          case (2)
4238                            dfdg3(iq,D3_RB_GAB_GBB) = val
4239                          case (3)
4240                            dfdg3(iq,D3_GAA_GAB_GBB) = val
4241                          case (4)
4242                            dfdg3(iq,D3_GAB_GAB_GBB) = val
4243                        end select
4244                      case (5)
4245                        select case (iv3)
4246                          case (1)
4247                            dfdg3(iq,D3_RA_GBB_GBB) = val
4248                          case (2)
4249                            dfdg3(iq,D3_RB_GBB_GBB) = val
4250                          case (3)
4251                            dfdg3(iq,D3_GAA_GBB_GBB) = val
4252                          case (4)
4253                            dfdg3(iq,D3_GAB_GBB_GBB) = val
4254                          case (5)
4255                            dfdg3(iq,D3_GBB_GBB_GBB) = val
4256                        end select
4257                    end select
4258                  case (6)
4259                    select case (iv2)
4260                      case (1)
4261                        select case (iv3)
4262                          case (1)
4263                            dfdt3(iq,D3_RA_RA_TA) = val
4264                        end select
4265                      case (2)
4266                        select case (iv3)
4267                          case (1)
4268                            dfdt3(iq,D3_RA_RB_TA) = val
4269                          case (2)
4270                            dfdt3(iq,D3_RB_RB_TA) = val
4271                        end select
4272                      case (3)
4273                        select case (iv3)
4274                          case (1)
4275                            dfdt3(iq,D3_RA_GAA_TA) = val
4276                          case (2)
4277                            dfdt3(iq,D3_RB_GAA_TA) = val
4278                          case (3)
4279                            dfdt3(iq,D3_GAA_GAA_TA) = val
4280                        end select
4281                      case (4)
4282                        select case (iv3)
4283                          case (1)
4284                            dfdt3(iq,D3_RA_GAB_TA) = val
4285                          case (2)
4286                            dfdt3(iq,D3_RB_GAB_TA) = val
4287                          case (3)
4288                            dfdt3(iq,D3_GAA_GAB_TA) = val
4289                          case (4)
4290                            dfdt3(iq,D3_GAB_GAB_TA) = val
4291                        end select
4292                      case (5)
4293                        select case (iv3)
4294                          case (1)
4295                            dfdt3(iq,D3_RA_GBB_TA) = val
4296                          case (2)
4297                            dfdt3(iq,D3_RB_GBB_TA) = val
4298                          case (3)
4299                            dfdt3(iq,D3_GAA_GBB_TA) = val
4300                          case (4)
4301                            dfdt3(iq,D3_GAB_GBB_TA) = val
4302                          case (5)
4303                            dfdt3(iq,D3_GBB_GBB_TA) = val
4304                        end select
4305                      case (6)
4306                        select case (iv3)
4307                          case (1)
4308                            dfdt3(iq,D3_RA_TA_TA) = val
4309                          case (2)
4310                            dfdt3(iq,D3_RB_TA_TA) = val
4311                          case (3)
4312                            dfdt3(iq,D3_GAA_TA_TA) = val
4313                          case (4)
4314                            dfdt3(iq,D3_GAB_TA_TA) = val
4315                          case (5)
4316                            dfdt3(iq,D3_GBB_TA_TA) = val
4317                          case (6)
4318                            dfdt3(iq,D3_TA_TA_TA) = val
4319                        end select
4320                    end select
4321                  case (7)
4322                    select case (iv2)
4323                      case (1)
4324                        select case (iv3)
4325                          case (1)
4326                            dfdt3(iq,D3_RA_RA_TB) = val
4327                        end select
4328                      case (2)
4329                        select case (iv3)
4330                          case (1)
4331                            dfdt3(iq,D3_RA_RB_TB) = val
4332                          case (2)
4333                            dfdt3(iq,D3_RB_RB_TB) = val
4334                        end select
4335                      case (3)
4336                        select case (iv3)
4337                          case (1)
4338                            dfdt3(iq,D3_RA_GAA_TB) = val
4339                          case (2)
4340                            dfdt3(iq,D3_RB_GAA_TB) = val
4341                          case (3)
4342                            dfdt3(iq,D3_GAA_GAA_TB) = val
4343                        end select
4344                      case (4)
4345                        select case (iv3)
4346                          case (1)
4347                            dfdt3(iq,D3_RA_GAB_TB) = val
4348                          case (2)
4349                            dfdt3(iq,D3_RB_GAB_TB) = val
4350                          case (3)
4351                            dfdt3(iq,D3_GAA_GAB_TB) = val
4352                          case (4)
4353                            dfdt3(iq,D3_GAB_GAB_TB) = val
4354                        end select
4355                      case (5)
4356                        select case (iv3)
4357                          case (1)
4358                            dfdt3(iq,D3_RA_GBB_TB) = val
4359                          case (2)
4360                            dfdt3(iq,D3_RB_GBB_TB) = val
4361                          case (3)
4362                            dfdt3(iq,D3_GAA_GBB_TB) = val
4363                          case (4)
4364                            dfdt3(iq,D3_GAB_GBB_TB) = val
4365                          case (5)
4366                            dfdt3(iq,D3_GBB_GBB_TB) = val
4367                        end select
4368                      case (6)
4369                        select case (iv3)
4370                          case (1)
4371                            dfdt3(iq,D3_RA_TA_TB) = val
4372                          case (2)
4373                            dfdt3(iq,D3_RB_TA_TB) = val
4374                          case (3)
4375                            dfdt3(iq,D3_GAA_TA_TB) = val
4376                          case (4)
4377                            dfdt3(iq,D3_GAB_TA_TB) = val
4378                          case (5)
4379                            dfdt3(iq,D3_GBB_TA_TB) = val
4380                          case (6)
4381                            dfdt3(iq,D3_TA_TA_TB) = val
4382                        end select
4383                      case (7)
4384                        select case (iv3)
4385                          case (1)
4386                            dfdt3(iq,D3_RA_TB_TB) = val
4387                          case (2)
4388                            dfdt3(iq,D3_RB_TB_TB) = val
4389                          case (3)
4390                            dfdt3(iq,D3_GAA_TB_TB) = val
4391                          case (4)
4392                            dfdt3(iq,D3_GAB_TB_TB) = val
4393                          case (5)
4394                            dfdt3(iq,D3_GBB_TB_TB) = val
4395                          case (6)
4396                            dfdt3(iq,D3_TA_TB_TB) = val
4397                          case (7)
4398                            dfdt3(iq,D3_TB_TB_TB) = val
4399                        end select
4400                    end select
4401                end select
4402              enddo
4403            enddo
4404          enddo
4405        enddo
4406C
4407      endif
4408C
4409      end
4410C>
4411C> \brief Evaluate the exchange-correlation energy and its 1st, 2nd
4412C> and 3rd partial derivatives
4413C>
4414      subroutine nwxc_eval_df3_doit(ipol,nq,rho,gamma,tau,f,
4415     +                               dfdr,dfdr2,dfdr3,
4416     +                               dfdg,dfdg2,dfdg3,
4417     +                               dfdt,dfdt2,dfdt3)
4418      use nwad3
4419      implicit none
4420#include "nwxcP.fh"
4421#include "nwxc_param.fh"
4422      integer ipol !< [Input] The number of spin channels
4423      integer nq   !< [Input] The number of points
4424C
4425      type(nwad_dble)::rho(nq,ipol)     !< [Input] Density
4426      type(nwad_dble)::gamma(nq,ipol+1) !< [Input] |Density gradient|^2
4427      type(nwad_dble)::tau(nq,ipol)     !< [Input] Kinetic energy
4428                                         !< density
4429C
4430      type(nwad_dble)::f(nq)           !< [Output] Energy
4431      double precision dfdr(nq,ipol)   !< [Output] Derivative wrt rho
4432      double precision dfdg(nq,ipol+1) !< [Output] Derivative wrt gamma
4433      double precision dfdt(nq,ipol)   !< [Output] Derivative wrt tau
4434c
4435      double precision dfdr2(nq,*)     !< [Output] 2nd derivative wrt
4436                                       !< rho
4437      double precision dfdg2(nq,*)     !< [Output] 2nd derivative wrt
4438                                       !< rho and gamma, and gamma
4439      double precision dfdt2(nq,*)     !< [Output] 2nd derivative wrt
4440                                       !< rho and tau, gamma and tau,
4441                                       !< and tau
4442c
4443      double precision dfdr3(nq,*)     !< [Output] 3rd derivative wrt
4444                                       !< rho
4445      double precision dfdg3(nq,*)     !< [Output] 3rd derivative wrt
4446                                       !< rho and gamma, and gamma
4447      double precision dfdt3(nq,*)     !< [Output] 3rd derivative wrt
4448                                       !< rho, gamm and tau
4449C
4450      integer iq !< Counter over points
4451      integer ip !< Counter over spin channels
4452      integer it !< Counter of functional terms
4453      integer n  !< Counter
4454C
4455      logical nwxc_is_gga  !< Is the functional a GGA
4456      logical nwxc_is_mgga !< Is the functional a meta-GGA
4457C
4458      integer nd1r(2) !< The number of partial derivatives wrt rho as
4459                      !< a function of ipol
4460      integer nd1g(2) !< The number of partial derivatives wrt gamma as
4461                      !< a function of ipol
4462      integer nd1t(2) !< The number of partial derivatives wrt tau as
4463                      !< a function of ipol
4464      integer nd2r(2) !< The number of 2nd partial derivatives wrt rho
4465                      !< as a function of ipol
4466      integer nd2g(2) !< The number of 2nd partial derivatives wrt
4467                      !< gamma as a function of ipol
4468      integer nd2t(2) !< The number of 2nd partial derivatives wrt tau
4469                      !< as a function of ipol
4470      integer nd3r(2) !< The number of 3rd partial derivatives wrt rho
4471                      !< as a function of ipol
4472      integer nd3g(2) !< The number of 3rd partial derivatives wrt
4473                      !< gamma as a function of ipol
4474      integer nd3t(2) !< The number of 3rd partial derivatives wrt rho
4475                      !< and tau as a function of ipol
4476      integer nd3gt(2)!< The number of 3rd partial derivatives wrt rho,
4477                      !< gamma and tau as a function of ipol
4478C
4479      external nwxc_k_dirac_d3
4480      external nwxc_k_becke88_d3
4481      external nwxc_k_pbe96_d3
4482c
4483      integer max_param
4484      parameter (max_param = 50)
4485      double precision param(max_param)
4486      double precision Axlsda
4487      parameter (Axlsda = -0.9305257363491d0 )
4488C
4489      data nd1r / D1_RA,  D1_RB  /
4490      data nd1g / D1_GAA, D1_GBB /
4491      data nd1t / D1_TA,  D1_TB  /
4492C
4493      data nd2r / D2_RA_RA,   D2_RB_RB   /
4494c      data nd2g / D2_GAA_GAA, D2_GBB_GBB /
4495      data nd2g / D2_GAA_GBB, D2_GBB_GBB /
4496      data nd2t / D2_TA_TA,   D2_TB_TB   /
4497C
4498      data nd3r  / D3_RA_RA_RA,    D3_RB_RB_RB    /
4499      data nd3g  / D3_GAA_GBB_GBB, D3_GBB_GBB_GBB /
4500      data nd3t  / D3_TA_TA_TA,    D3_TB_TB_TB    /
4501      data nd3gt / D3_GAA_TB_TB,   D3_GBB_TB_TB   /
4502C
4503      do iq = 1, nq
4504        f(iq) = 0.0d0
4505      enddo
4506C
4507      do it = 1, nwxc_num_f
4508        select case (nwxc_ids(it))
4509          case (NWXCP_X_SLATER)
4510            call nwxc_x_dirac_d3(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
4511     +                           rho,f)
4512          case (NWXCP_X_B86b)
4513            call nwxc_x_b86b_d3(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
4514     +                          rho,gamma,f)
4515          case (NWXCP_X_B88)
4516            call nwxc_x_b88_d3(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
4517     +                         rho,gamma,f)
4518          case (NWXCP_X_B97)
4519            param(1) = 2.0d0
4520            param(2) = 0.80940d+00
4521            param(3) = 0.50730d+00
4522            param(4) = 0.74810d+00
4523            call nwxc_x_b97_d3(param,nwxc_rho_tol,ipol,nq,
4524     +                         nwxc_wghts(it),rho,gamma,f)
4525          case (NWXCP_X_B97_1)
4526            param(1) = 2.0d0
4527            param(2) = 0.789518d+00
4528            param(3) = 0.573805d+00
4529            param(4) = 0.660975d+00
4530            call nwxc_x_b97_d3(param,nwxc_rho_tol,ipol,nq,
4531     +                         nwxc_wghts(it),rho,gamma,f)
4532          case (NWXCP_X_B97_2)
4533            param(1) = 2.0d0
4534            param(2) = 0.827642D+00
4535            param(3) = 0.478400D-01
4536            param(4) = 0.176125D+01
4537            call nwxc_x_b97_d3(param,nwxc_rho_tol,ipol,nq,
4538     +                         nwxc_wghts(it),rho,gamma,f)
4539          case (NWXCP_X_B97_3)
4540            param(1) = 4.0d0
4541            param(2) = 7.334648D-01
4542            param(3) = 2.925270D-01
4543            param(4) = 3.338789D+00
4544            param(5) =-1.051158D+01
4545            param(6) = 1.060907D+01
4546            call nwxc_x_b97_d3(param,nwxc_rho_tol,ipol,nq,
4547     +                         nwxc_wghts(it),rho,gamma,f)
4548          case (NWXCP_X_B97_D)
4549            param(1) = 2.0d0
4550            param(2) = 1.086620d+0
4551            param(3) =-0.521270d+00
4552            param(4) = 3.254290d+00
4553            call nwxc_x_b97_d3(param,nwxc_rho_tol,ipol,nq,
4554     +                         nwxc_wghts(it),rho,gamma,f)
4555          case (NWXCP_X_B97_G)
4556            param(1) = 2.0d0
4557            param(2) = 1.1068d0
4558            param(3) =-0.8765d0
4559            param(4) = 4.2639d0
4560            call nwxc_x_b97_d3(param,nwxc_rho_tol,ipol,nq,
4561     +                         nwxc_wghts(it),rho,gamma,f)
4562          case (NWXCP_X_B98)
4563            param(1) = 2.0d0
4564            param(2) = 0.790194d00
4565            param(3) = 0.400271d00
4566            param(4) = 0.832857d00
4567            call nwxc_x_b97_d3(param,nwxc_rho_tol,ipol,nq,
4568     +                         nwxc_wghts(it),rho,gamma,f)
4569          case (NWXCP_X_BNL)
4570            param(1) = nwxc_cam_gamma
4571            call nwxc_x_bnl_d3(param,nwxc_rho_tol,ipol,nq,
4572     +                         nwxc_wghts(it),rho,f)
4573          case (NWXCP_X_CAMB88)
4574            param(1) = nwxc_cam_alpha
4575            param(2) = nwxc_cam_beta
4576            param(3) = nwxc_cam_gamma
4577            call nwxc_x_camb88_d3(param,nwxc_rho_tol,ipol,nq,
4578     +                            nwxc_wghts(it),rho,gamma,f)
4579          case (NWXCP_X_CAMLSD)
4580            param(1) = nwxc_cam_alpha
4581            param(2) = nwxc_cam_beta
4582            param(3) = nwxc_cam_gamma
4583            call nwxc_x_camlsd_d3(param,nwxc_rho_tol,ipol,nq,
4584     +                            nwxc_wghts(it),rho,f)
4585          case (NWXCP_X_CAMPBE)
4586            param(1) = 0.8040d0
4587            param(2) = 0.2195149727645171d0
4588            param(3) = nwxc_cam_alpha
4589            param(4) = nwxc_cam_beta
4590            param(5) = nwxc_cam_gamma
4591            call nwxc_x_campbe_d3(param,nwxc_rho_tol,ipol,nq,
4592     +                            nwxc_wghts(it),rho,gamma,f)
4593          case (NWXCP_X_CAMREVPBE)
4594            param(1) = 1.245d0
4595            param(2) = 0.2195149727645171d0
4596            param(3) = nwxc_cam_alpha
4597            param(4) = nwxc_cam_beta
4598            param(5) = nwxc_cam_gamma
4599            call nwxc_x_campbe_d3(param,nwxc_rho_tol,ipol,nq,
4600     +                            nwxc_wghts(it),rho,gamma,f)
4601          case (NWXCP_X_CAMRPBE)
4602            param(1) = nwxc_cam_alpha
4603            param(2) = nwxc_cam_beta
4604            param(3) = nwxc_cam_gamma
4605            call nwxc_x_camrpbe_d3(param,nwxc_rho_tol,ipol,nq,
4606     +                             nwxc_wghts(it),rho,gamma,f)
4607          case (NWXCP_X_CAMS12G)
4608            param(1) = 1.03323556d0
4609            param(2) = 0.757d0
4610            param(3) = 0.00417251d0
4611            param(4) = 0.00115216d0
4612            param(5) = 0.00706184d0
4613            param(6) = nwxc_cam_alpha
4614            param(7) = nwxc_cam_beta
4615            param(8) = nwxc_cam_gamma
4616            call nwxc_x_cams12_d3(param,nwxc_rho_tol,ipol,nq,
4617     +                            nwxc_wghts(it),rho,gamma,f)
4618          case (NWXCP_X_CAMS12H)
4619            param(1) = 1.02149642d0
4620            param(2) = 0.757d0
4621            param(3) = 0.00825905d0
4622            param(4) = 0.00235804d0
4623            param(5) = 0.00654977d0
4624            param(6) = nwxc_cam_alpha
4625            param(7) = nwxc_cam_beta
4626            param(8) = nwxc_cam_gamma
4627            call nwxc_x_cams12_d3(param,nwxc_rho_tol,ipol,nq,
4628     +                            nwxc_wghts(it),rho,gamma,f)
4629          case (NWXCP_X_DLDF)
4630            call nwxc_x_dldf_d3(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
4631     +                          rho,gamma,tau,f)
4632          case (NWXCP_X_FT97)
4633            call nwxc_x_ft97_d3(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
4634     +                          rho,gamma,f)
4635          case (NWXCP_X_GILL)
4636            call nwxc_x_gill_d3(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
4637     +                          rho,gamma,f)
4638          case (NWXCP_X_HCTH)
4639            param(1) = 4.0d0
4640            param(2) = 0.109320d+01
4641            param(3) =-0.744056d+00
4642            param(4) = 0.559920d+01
4643            param(5) =-0.678549d+01
4644            param(6) = 0.449357d+01
4645            call nwxc_x_b97_d3(param,nwxc_rho_tol,ipol,nq,
4646     +                         nwxc_wghts(it),rho,gamma,f)
4647          case (NWXCP_X_HCTH120)
4648            param(1) = 4.0d0
4649            param(2) = 1.09163d0
4650            param(3) =-0.74720d0
4651            param(4) = 5.07830d0
4652            param(5) =-4.10750d0
4653            param(6) = 1.17170d0
4654            call nwxc_x_b97_d3(param,nwxc_rho_tol,ipol,nq,
4655     +                         nwxc_wghts(it),rho,gamma,f)
4656          case (NWXCP_X_HCTH147)
4657            param(1) = 4.0d0
4658            param(2) = 1.09025d0
4659            param(3) =-0.79920d0
4660            param(4) = 5.57210d0
4661            param(5) =-5.86760d0
4662            param(6) = 3.04540d0
4663            call nwxc_x_b97_d3(param,nwxc_rho_tol,ipol,nq,
4664     +                         nwxc_wghts(it),rho,gamma,f)
4665          case (NWXCP_X_HCTH407)
4666            param(1) = 4.0d0
4667            param(2) = 1.08184d0
4668            param(3) =-0.5183d0
4669            param(4) = 3.4256d0
4670            param(5) =-2.6290d0
4671            param(6) = 2.2886d0
4672            call nwxc_x_b97_d3(param,nwxc_rho_tol,ipol,nq,
4673     +                         nwxc_wghts(it),rho,gamma,f)
4674          case (NWXCP_X_HCTH407P)
4675            param(1) = 4.0d0
4676            param(2) = 1.08018D0
4677            param(3) =-0.4117D0
4678            param(4) = 2.4368D0
4679            param(5) = 1.3890D0
4680            param(6) =-1.3529D0
4681            call nwxc_x_b97_d3(param,nwxc_rho_tol,ipol,nq,
4682     +                         nwxc_wghts(it),rho,gamma,f)
4683          case (NWXCP_X_HCTH_A)
4684            param(1) = 2.0d0
4685            param(2) = 0.109878d+01
4686            param(3) =-0.251173d+01
4687            param(4) = 0.156233d-01
4688            call nwxc_x_b97_d3(param,nwxc_rho_tol,ipol,nq,
4689     +                         nwxc_wghts(it),rho,gamma,f)
4690          case (NWXCP_X_HCTHP14)
4691            param(1) = 4.0d0
4692            param(2) = 0.103161d+01
4693            param(3) =-0.360781d+00
4694            param(4) = 0.351994d+01
4695            param(5) =-0.495944d+01
4696            param(6) = 0.241165d+01
4697            call nwxc_x_b97_d3(param,nwxc_rho_tol,ipol,nq,
4698     +                         nwxc_wghts(it),rho,gamma,f)
4699           case (NWXCP_X_M05)
4700             param( 1) =    0.08151d0
4701             param( 2) =   -0.43956d0
4702             param( 3) =   -3.22422d0
4703             param( 4) =    2.01819d0
4704             param( 5) =    8.79431d0
4705             param( 6) =   -0.00295d0
4706             param( 7) =    9.82029d0
4707             param( 8) =   -4.82351d0
4708             param( 9) =  -48.17574d0
4709             param(10) =    3.64802d0
4710             param(11) =   34.02248d0
4711             call nwxc_x_m05_d3(param,nwxc_rho_tol,ipol,nq,
4712     +            nwxc_wghts(it),rho,gamma,tau,f)
4713           case (NWXCP_X_M05_2X)
4714             param( 1) =   -0.56833d0
4715             param( 2) =   -1.30057d0
4716             param( 3) =    5.50070d0
4717             param( 4) =    9.06402d0
4718             param( 5) =  -32.21075d0
4719             param( 6) =  -23.73298d0
4720             param( 7) =   70.22996d0
4721             param( 8) =   29.88614d0
4722             param( 9) =  -60.25778d0
4723             param(10) =  -13.22205d0
4724             param(11) =   15.23694d0
4725             call nwxc_x_m05_d3(param,nwxc_rho_tol,ipol,nq,
4726     +            nwxc_wghts(it),rho,gamma,tau,f)
4727           case (NWXCP_X_M06)
4728             param( 1) =  1.422057D-01*Axlsda
4729             param( 2) =  7.370319D-04*Axlsda
4730             param( 3) = -1.601373D-02*Axlsda
4731             param( 4) =  0.000000D+00
4732             param( 5) =  0.000000D+00
4733             param( 6) =  0.000000D+00
4734             param( 7) =  5.877943D-01
4735             param( 8) = -1.371776D-01
4736             param( 9) =  2.682367D-01
4737             param(10) = -2.515898D+00
4738             param(11) = -2.978892D+00
4739             param(12) =  8.710679D+00
4740             param(13) =  1.688195D+01
4741             param(14) = -4.489724D+00
4742             param(15) = -3.299983D+01
4743             param(16) = -1.449050D+01
4744             param(17) =  2.043747D+01
4745             param(18) =  1.256504D+01
4746             call nwxc_x_m06_d3(param,nwxc_rho_tol,ipol,nq,
4747     +            nwxc_wghts(it),rho,gamma,tau,f)
4748           case (NWXCP_X_M06_HF)
4749             param( 1) = -1.179732D-01*Axlsda
4750             param( 2) = -2.500000D-03*Axlsda
4751             param( 3) = -1.180065D-02*Axlsda
4752             param( 4) =  0.000000D+00
4753             param( 5) =  0.000000D+00
4754             param( 6) =  0.000000D+00
4755             param( 7) =  1.179732D-01
4756             param( 8) = -1.066708D+00
4757             param( 9) = -1.462405D-01
4758             param(10) =  7.481848D+00
4759             param(11) =  3.776679D+00
4760             param(12) = -4.436118D+01
4761             param(13) = -1.830962D+01
4762             param(14) =  1.003903D+02
4763             param(15) =  3.864360D+01
4764             param(16) = -9.806018D+01
4765             param(17) = -2.557716D+01
4766             param(18) =  3.590404D+01
4767             call nwxc_x_m06_d3(param,nwxc_rho_tol,ipol,nq,
4768     +            nwxc_wghts(it),rho,gamma,tau,f)
4769           case (NWXCP_X_M06_L)
4770             param( 1) =  6.012244D-01*Axlsda
4771             param( 2) =  4.748822D-03*Axlsda
4772             param( 3) = -8.635108D-03*Axlsda
4773             param( 4) = -9.308062D-06*Axlsda
4774             param( 5) =  4.482811D-05*Axlsda
4775             param( 6) =  0.000000D+00
4776             param( 7) =  3.987756D-01
4777             param( 8) =  2.548219D-01
4778             param( 9) =  3.923994D-01
4779             param(10) = -2.103655D+00
4780             param(11) = -6.302147D+00
4781             param(12) =  1.097615D+01
4782             param(13) =  3.097273D+01
4783             param(14) = -2.318489D+01
4784             param(15) = -5.673480D+01
4785             param(16) =  2.160364D+01
4786             param(17) =  3.421814D+01
4787             param(18) = -9.049762D+00
4788             call nwxc_x_m06_d3(param,nwxc_rho_tol,ipol,nq,
4789     +            nwxc_wghts(it),rho,gamma,tau,f)
4790           case (NWXCP_X_M06_2X)
4791             param( 1) =  4.600000D-01
4792             param( 2) = -2.206052D-01
4793             param( 3) = -9.431788D-02
4794             param( 4) =  2.164494D+00
4795             param( 5) = -2.556466D+00
4796             param( 6) = -1.422133D+01
4797             param( 7) =  1.555044D+01
4798             param( 8) =  3.598078D+01
4799             param( 9) = -2.722754D+01
4800             param(10) = -3.924093D+01
4801             param(11) =  1.522808D+01
4802             param(12) =  1.522227D+01
4803             call nwxc_x_m06_2x_d3(param,nwxc_rho_tol,ipol,nq,
4804     +            nwxc_wghts(it),rho,gamma,tau,f)
4805           case (NWXCP_X_M08_HX)
4806c            parameters A
4807             param(01) =  1.3340172D+00
4808             param(02) = -9.4751087D+00
4809             param(03) = -1.2541893D+01
4810             param(04) =  9.1369974D+00
4811             param(05) =  3.4717204D+01
4812             param(06) =  5.8831807D+01
4813             param(07) =  7.1369574D+01
4814             param(08) =  2.3312961D+01
4815             param(09) =  4.8314679D+00
4816             param(10) = -6.5044167D+00
4817             param(11) = -1.4058265D+01
4818             param(12) =  1.2880570D+01
4819c            parameters B
4820             param(13) = -8.5631823D-01
4821             param(14) =  9.2810354D+00
4822             param(15) =  1.2260749D+01
4823             param(16) = -5.5189665D+00
4824             param(17) = -3.5534989D+01
4825             param(18) = -8.2049996D+01
4826             param(19) = -6.8586558D+01
4827             param(20) =  3.6085694D+01
4828             param(21) = -9.3740983D+00
4829             param(22) = -5.9731688D+01
4830             param(23) =  1.6587868D+01
4831             param(24) =  1.3993203D+01
4832c            parameters C and D
4833             do n = 25, 48
4834               param(n) = 0.0d0
4835             enddo
4836             call nwxc_x_m08_d3(param,nwxc_rho_tol,ipol,nq,
4837     +            nwxc_wghts(it),rho,gamma,tau,f)
4838           case (NWXCP_X_M08_SO)
4839c            parameters A
4840             param(01) = -3.4888428D-01
4841             param(02) = -5.8157416D+00
4842             param(03) =  3.7550810D+01
4843             param(04) =  6.3727406D+01
4844             param(05) = -5.3742313D+01
4845             param(06) = -9.8595529D+01
4846             param(07) =  1.6282216D+01
4847             param(08) =  1.7513468D+01
4848             param(09) = -6.7627553D+00
4849             param(10) =  1.1106658D+01
4850             param(11) =  1.5663545D+00
4851             param(12) =  8.7603470D+00
4852c            parameters B
4853             param(13) =  7.8098428D-01
4854             param(14) =  5.4538178D+00
4855             param(15) = -3.7853348D+01
4856             param(16) = -6.2295080D+01
4857             param(17) =  4.6713254D+01
4858             param(18) =  8.7321376D+01
4859             param(19) =  1.6053446D+01
4860             param(20) =  2.0126920D+01
4861             param(21) = -4.0343695D+01
4862             param(22) = -5.8577565D+01
4863             param(23) =  2.0890272D+01
4864             param(24) =  1.0946903D+01
4865c            parameters C and D
4866             do n = 25, 48
4867               param(n) = 0.0d0
4868             enddo
4869             call nwxc_x_m08_d3(param,nwxc_rho_tol,ipol,nq,
4870     +            nwxc_wghts(it),rho,gamma,tau,f)
4871           case (NWXCP_X_M11)
4872c            parameters A
4873             param(01) = -0.18399900D+00
4874             param(02) = -1.39046703D+01
4875             param(03) =  1.18206837D+01
4876             param(04) =  3.10098465D+01
4877             param(05) = -5.19625696D+01
4878             param(06) =  1.55750312D+01
4879             param(07) = -6.94775730D+00
4880             param(08) = -1.58465014D+02
4881             param(09) = -1.48447565D+00
4882             param(10) =  5.51042124D+01
4883             param(11) = -1.34714184D+01
4884             param(12) =  0.000000D+00
4885c            parameters B
4886             param(13) =  0.75599900D+00
4887             param(14) =  1.37137944D+01
4888             param(15) = -1.27998304D+01
4889             param(16) = -2.93428814D+01
4890             param(17) =  5.91075674D+01
4891             param(18) = -2.27604866D+01
4892             param(19) = -1.02769340D+01
4893             param(20) =  1.64752731D+02
4894             param(21) =  1.85349258D+01
4895             param(22) = -5.56825639D+01
4896             param(23) =  7.47980859D+00
4897             param(24) =  0.000000D+00
4898c            parameters C and D
4899             do n = 25, 48
4900               param(n) = 0.0d0
4901             enddo
4902             call nwxc_x_m11_d3(param,nwxc_rho_tol,ipol,nq,
4903     +            nwxc_wghts(it),rho,gamma,tau,f)
4904           case (NWXCP_X_M11_L)
4905c            parameters A
4906             param(01) =  8.121131D-01
4907             param(02) =  1.738124D+01
4908             param(03) =  1.154007D+00
4909             param(04) =  6.869556D+01
4910             param(05) =  1.016864D+02
4911             param(06) = -5.887467D+00
4912             param(07) =  4.517409D+01
4913             param(08) = -2.773149D+00
4914             param(09) = -2.617211D+01
4915             param(10) =  0.000000D+00
4916             param(11) =  0.000000D+00
4917             param(12) =  0.000000D+00
4918c            parameters B
4919             param(13) =  1.878869D-01
4920             param(14) = -1.653877D+01
4921             param(15) =  6.755753D-01
4922             param(16) = -7.567572D+01
4923             param(17) = -1.040272D+02
4924             param(18) =  1.831853D+01
4925             param(19) = -5.573352D+01
4926             param(20) = -3.520210D+00
4927             param(21) =  3.724276D+01
4928             param(22) =  0.000000D+00
4929             param(23) =  0.000000D+00
4930             param(24) =  0.000000D+00
4931c            parameters C
4932             param(25) = -4.386615D-01
4933             param(26) = -1.214016D+02
4934             param(27) = -1.393573D+02
4935             param(28) = -2.046649D+00
4936             param(29) =  2.804098D+01
4937             param(30) = -1.312258D+01
4938             param(31) = -6.361819D+00
4939             param(32) = -8.055758D-01
4940             param(33) =  3.736551D+00
4941             param(34) =  0.000000D+00
4942             param(35) =  0.000000D+00
4943             param(36) =  0.000000D+00
4944c            parameters D
4945             param(37) =  1.438662D+00
4946             param(38) =  1.209465D+02
4947             param(39) =  1.328252D+02
4948             param(40) =  1.296355D+01
4949             param(41) =  5.854866D+00
4950             param(42) = -3.378162D+00
4951             param(43) = -4.423393D+01
4952             param(44) =  6.844475D+00
4953             param(45) =  1.949541D+01
4954             param(46) =  0.000000D+00
4955             param(47) =  0.000000D+00
4956             param(48) =  0.000000D+00
4957             call nwxc_x_m11_d3(param,nwxc_rho_tol,ipol,nq,
4958     +            nwxc_wghts(it),rho,gamma,tau,f)
4959           case (NWXCP_X_MPW91)
4960             param(1) = 3.72d0
4961             param(2) = 0.00426D0
4962             call nwxc_x_pw91_d3(param,nwxc_rho_tol,ipol,nq,
4963     +                           nwxc_wghts(it),rho,gamma,f)
4964           case (NWXCP_X_OPT)
4965             call nwxc_x_opt_d3(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
4966     +                          rho,gamma,f)
4967           case (NWXCP_X_PW6B95)
4968             param(1) = 0.00538d0
4969             param(2) = 1.7382d0
4970             param(3) = 3.8901d0
4971             call nwxc_x_pw6_d3(param,nwxc_rho_tol,ipol,nq,
4972     +                          nwxc_wghts(it),rho,gamma,f)
4973           case (NWXCP_X_PWB6K)
4974             param(1) = 0.00539d0
4975             param(2) = 1.7077d0
4976             param(3) = 4.0876d0
4977             call nwxc_x_pw6_d3(param,nwxc_rho_tol,ipol,nq,
4978     +                          nwxc_wghts(it),rho,gamma,f)
4979           case (NWXCP_X_PW91)
4980             param(1) = 4.0d0
4981             param(2) = 0.0042D0
4982             call nwxc_x_pw91_d3(param,nwxc_rho_tol,ipol,nq,
4983     +                           nwxc_wghts(it),rho,gamma,f)
4984           case (NWXCP_X_PBE)
4985             param(1) = 0.8040d0
4986             param(2) = 0.2195149727645171d0
4987             call nwxc_x_pbe_d3(param,nwxc_rho_tol,ipol,nq,
4988     +                          nwxc_wghts(it),rho,gamma,f)
4989           case (NWXCP_X_PBESOL)
4990             param(1) = 0.8040d0
4991             param(2) = 10.0d0/81.0d0
4992             call nwxc_x_pbe_d3(param,nwxc_rho_tol,ipol,nq,
4993     +                          nwxc_wghts(it),rho,gamma,f)
4994           case (NWXCP_X_REVPBE)
4995             param(1) = 1.245d0
4996             param(2) = 0.2195149727645171d0
4997             call nwxc_x_pbe_d3(param,nwxc_rho_tol,ipol,nq,
4998     +                          nwxc_wghts(it),rho,gamma,f)
4999           case (NWXCP_X_RPBE)
5000             call nwxc_x_rpbe_d3(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
5001     +                           rho,gamma,f)
5002           case (NWXCP_X_PKZB)
5003             call nwxc_x_pkzb99_d3(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
5004     +                             rho,gamma,tau,f)
5005           case (NWXCP_X_S12G)
5006             param(1) = 1.03842032d0
5007             param(2) = 0.757d0
5008             param(3) = 0.00403198d0
5009             param(4) = 0.00104596d0
5010             param(5) = 0.00594635d0
5011             call nwxc_x_s12_d3(param,nwxc_rho_tol,ipol,nq,
5012     +                          nwxc_wghts(it),rho,gamma,f)
5013           case (NWXCP_X_S12H)
5014             param(1) = 1.02543951d0
5015             param(2) = 0.757d0
5016             param(3) = 0.00761554d0
5017             param(4) = 0.00211063d0
5018             param(5) = 0.00604672d0
5019             call nwxc_x_s12_d3(param,nwxc_rho_tol,ipol,nq,
5020     +                          nwxc_wghts(it),rho,gamma,f)
5021           case (NWXCP_X_SOGGA)
5022             param(1)  =  0.5d0
5023             param(2)  =  0.276d0
5024             param(3)  =  0.0d0
5025             param(4)  =  0.0d0
5026             param(5)  =  0.0d0
5027             param(6)  =  0.0d0
5028             param(7)  =  0.5d0
5029             param(8)  =  0.276d0
5030             param(9)  =  0.0d0
5031             param(10) =  0.0d0
5032             param(11) =  0.0d0
5033             param(12) =  0.0d0
5034             call nwxc_x_sogga_d3(param,nwxc_rho_tol,ipol,nq,
5035     +                            nwxc_wghts(it),rho,gamma,f)
5036           case (NWXCP_X_SOGGA11)
5037             param(1)  =  0.5d0
5038             param(2)  = -2.95535d0
5039             param(3)  =  15.7974d0
5040             param(4)  = -91.1804d0
5041             param(5)  =  96.2030d0
5042             param(6)  =  0.18683d0
5043             param(7)  =  0.50000d0
5044             param(8)  =  3.50743d0
5045             param(9)  = -12.9523d0
5046             param(10) =  49.7870d0
5047             param(11) = -33.2545d0
5048             param(12) = -11.1396d0
5049             call nwxc_x_sogga_d3(param,nwxc_rho_tol,ipol,nq,
5050     +                            nwxc_wghts(it),rho,gamma,f)
5051           case (NWXCP_X_SOGGA11_X)
5052             param(1)  =  2.99250d-01
5053             param(2)  =  3.21638d+00
5054             param(3)  = -3.55605d+00
5055             param(4)  =  7.65852d+00
5056             param(5)  = -1.12830d+01
5057             param(6)  =  5.25813d+00
5058             param(7)  =  2.99250d-01
5059             param(8)  = -2.88595d+00
5060             param(9)  =  3.23617d+00
5061             param(10) = -2.45393d+00
5062             param(11) = -3.75495d+00
5063             param(12) =  3.96613d+00
5064             call nwxc_x_sogga_d3(param,nwxc_rho_tol,ipol,nq,
5065     +                            nwxc_wghts(it),rho,gamma,f)
5066           case (NWXCP_X_SSB_D)
5067             call nwxc_x_ssbD_1_d3(nwxc_rho_tol,ipol,nq,
5068     +                             nwxc_wghts(it),rho,gamma,f)
5069           case (NWXCP_X_TPSS)
5070             call nwxc_x_tpss03_d3(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
5071     +                             rho,gamma,tau,f)
5072          case (NWXCP_X_WPBE)
5073            param(1) = nwxc_cam_gamma
5074            call nwxc_x_wpbe_d3(param,nwxc_rho_tol,ipol,nq,
5075     +                          nwxc_wghts(it),rho,gamma,f)
5076           case (NWXCP_X_VS98)
5077             param(1) =  -9.800683d-01
5078             param(2) =  -3.556788d-03
5079             param(3) =   6.250326d-03
5080             param(4) =  -2.354518d-05
5081             param(5) =  -1.282732d-04
5082             param(6) =   3.574822d-04
5083             call nwxc_x_vs98_d3(param,nwxc_rho_tol,ipol,nq,
5084     +            nwxc_wghts(it),rho,gamma,tau,f)
5085           case (NWXCP_C_B95)
5086             param(1) = 0.0031d0
5087             param(2) = 0.038d0
5088             call nwxc_c_b95_d3(param,nwxc_rho_tol,ipol,nq,
5089     +                          nwxc_wghts(it),rho,gamma,tau,f)
5090           case (NWXCP_C_B97)
5091             param(1) = 2.0d0
5092             param(2) = 0.17370d+00
5093             param(3) = 0.94540d+00
5094             param(4) = 0.23487d+01
5095             param(5) = 0.74710d+00
5096             param(6) =-0.24868d+01
5097             param(7) =-0.45961d+01
5098             call nwxc_c_b97_d3(param,nwxc_rho_tol,ipol,nq,
5099     +                          nwxc_wghts(it),rho,gamma,f)
5100           case (NWXCP_C_B97_1)
5101             param(1) = 2.0d0
5102             param(2) = 0.820011d-01
5103             param(3) = 0.955689d+00
5104             param(4) = 0.271681d+01
5105             param(5) = 0.788552d+00
5106             param(6) =-0.287103d+01
5107             param(7) =-0.547869d+01
5108             call nwxc_c_b97_d3(param,nwxc_rho_tol,ipol,nq,
5109     +                          nwxc_wghts(it),rho,gamma,f)
5110           case (NWXCP_C_B97_2)
5111             param(1) = 2.0d0
5112             param(2) = 0.585808D+00
5113             param(3) = 0.999849D+00
5114             param(4) =-0.691682D+00
5115             param(5) = 0.140626D+01
5116             param(6) = 0.394796D+00
5117             param(7) =-0.744060D+01
5118             call nwxc_c_b97_d3(param,nwxc_rho_tol,ipol,nq,
5119     +                          nwxc_wghts(it),rho,gamma,f)
5120           case (NWXCP_C_B97_3)
5121             param(1)  = 4.0d0
5122             param(2)  = 5.623649D-01
5123             param(3)  = 1.133830D+00
5124             param(4)  =-1.322980D+00
5125             param(5)  =-2.811967D+00
5126             param(6)  = 6.359191D+00
5127             param(7)  = 7.431302D+00
5128             param(8)  =-7.464002D+00
5129             param(9)  =-1.969342D+00
5130             param(10) = 1.827082D+00
5131             param(11) =-1.174423D+01
5132             call nwxc_c_b97_d3(param,nwxc_rho_tol,ipol,nq,
5133     +                          nwxc_wghts(it),rho,gamma,f)
5134           case (NWXCP_C_B97_D)
5135             param(1) = 2.0d0
5136             param(2) = 0.22340d+00
5137             param(3) = 0.690410d+00
5138             param(4) =-1.562080d+00
5139             param(5) = 6.302700d00
5140             param(6) = 1.942930d+0
5141             param(7) =-14.97120d+00
5142             call nwxc_c_b97_d3(param,nwxc_rho_tol,ipol,nq,
5143     +                          nwxc_wghts(it),rho,gamma,f)
5144           case (NWXCP_C_B97_G)
5145             param(1) = 2.0d0
5146             param(2) = 0.4883d0
5147             param(3) = 0.7961d0
5148             param(4) =-2.117d0
5149             param(5) = 5.7060d0
5150             param(6) = 2.3235d0
5151             param(7) =-14.9820d0
5152             call nwxc_c_b97_d3(param,nwxc_rho_tol,ipol,nq,
5153     +                          nwxc_wghts(it),rho,gamma,f)
5154           case (NWXCP_C_B98)
5155             param(1) = 2.0d0
5156             param(2) =-0.120163d00
5157             param(3) = 0.934715d00
5158             param(4) = 2.82332d0
5159             param(5) = 1.14105d0
5160             param(6) =-2.59412d0
5161             param(7) =-5.33398d0
5162             call nwxc_c_b97_d3(param,nwxc_rho_tol,ipol,nq,
5163     +                          nwxc_wghts(it),rho,gamma,f)
5164           case (NWXCP_C_DLDF)
5165             call nwxc_c_dldf_d3(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
5166     +                           rho,gamma,tau,f)
5167           case (NWXCP_C_FT97)
5168             call nwxc_c_ft97_d3(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
5169     +                           rho,gamma,f)
5170           case (NWXCP_C_HCTH)
5171             param(1)  = 4.0d0
5172             param(2)  = 0.222601d0
5173             param(3)  = 0.729974d0
5174             param(4)  =-3.38622d-002
5175             param(5)  = 3.352870d0
5176             param(6)  =-1.25170d-002
5177             param(7)  =-11.543d0
5178             param(8)  =-0.802496d0
5179             param(9)  = 8.085640d0
5180             param(10) = 1.553960d0
5181             param(11) =-4.478570d0
5182             call nwxc_c_b97_d3(param,nwxc_rho_tol,ipol,nq,
5183     +                          nwxc_wghts(it),rho,gamma,f)
5184           case (NWXCP_C_HCTH120)
5185             param(1)  = 4.0d0
5186             param(2)  = 0.48951d0
5187             param(3)  = 0.51473d0
5188             param(4)  =-0.26070d0
5189             param(5)  = 6.92980d0
5190             param(6)  = 0.43290d0
5191             param(7)  =-24.7070d0
5192             param(8)  =-1.99250d0
5193             param(9)  = 23.1100d0
5194             param(10) = 2.48530d0
5195             param(11) =-11.3230d0
5196             call nwxc_c_b97_d3(param,nwxc_rho_tol,ipol,nq,
5197     +                          nwxc_wghts(it),rho,gamma,f)
5198           case (NWXCP_C_HCTH147)
5199             param(1)  = 4.0d0
5200             param(2)  = 0.56258d0
5201             param(3)  = 0.54235d0
5202             param(4)  =-1.71000d-002
5203             param(5)  = 7.01460d0
5204             param(6)  =-1.30640d0
5205             param(7)  =-28.3820d0
5206             param(8)  = 1.05750d0
5207             param(9)  = 35.0330d0
5208             param(10) = 0.88540d0
5209             param(11) =-20.4280d0
5210             call nwxc_c_b97_d3(param,nwxc_rho_tol,ipol,nq,
5211     +                          nwxc_wghts(it),rho,gamma,f)
5212           case (NWXCP_C_HCTH407)
5213             param(1)  = 4.0d0
5214             param(2)  = 1.18777d0
5215             param(3)  = 0.58908d0
5216             param(4)  =-2.40290d0
5217             param(5)  = 4.42370d0
5218             param(6)  = 5.61740d0
5219             param(7)  =-19.2220d0
5220             param(8)  =-9.17920d0
5221             param(9)  = 42.5720d0
5222             param(10) = 6.24800d0
5223             param(11) =-42.0050d0
5224             call nwxc_c_b97_d3(param,nwxc_rho_tol,ipol,nq,
5225     +                          nwxc_wghts(it),rho,gamma,f)
5226           case (NWXCP_C_HCTH407P)
5227             param(1)  = 4.0d0
5228             param(2)  = 0.80302d0
5229             param(3)  = 0.73604d0
5230             param(4)  =-1.04790d0
5231             param(5)  = 3.02700d0
5232             param(6)  = 4.98070d0
5233             param(7)  =-10.0750d0
5234             param(8)  =-12.8900d0
5235             param(9)  = 20.6110d0
5236             param(10) = 9.64460d0
5237             param(11) =-29.4180d0
5238             call nwxc_c_b97_d3(param,nwxc_rho_tol,ipol,nq,
5239     +                          nwxc_wghts(it),rho,gamma,f)
5240           case (NWXCP_C_HCTH_A)
5241             param(1)  = 4.0d0
5242             param(2)  = 1.36823d-002
5243             param(3)  = 0.836897d0
5244             param(4)  = 0.268920d0
5245             param(5)  = 1.720510d0
5246             param(6)  =-0.550769d0
5247             param(7)  =-2.784980d0
5248             param(8)  = 1.039470d0
5249             param(9)  =-4.575040d0
5250             param(10) = 0.000000d0
5251             param(11) = 0.000000d0
5252             call nwxc_c_b97_d3(param,nwxc_rho_tol,ipol,nq,
5253     +                          nwxc_wghts(it),rho,gamma,f)
5254           case (NWXCP_C_HCTHP14)
5255             param(1)  = 4.0d0
5256             param(2)  = 2.82414d0
5257             param(3)  = 8.21827d-002
5258             param(4)  = 3.18843d-002
5259             param(5)  = 4.56466d0
5260             param(6)  =-1.78512d0
5261             param(7)  =-13.5529d0
5262             param(8)  = 2.39795d0
5263             param(9)  = 13.3820d0
5264             param(10) =-0.876909d0
5265             param(11) =-3.174930d0
5266             call nwxc_c_b97_d3(param,nwxc_rho_tol,ipol,nq,
5267     +                          nwxc_wghts(it),rho,gamma,f)
5268           case (NWXCP_C_M05)
5269             param( 1) =   1.00000d0
5270             param( 2) =   3.78569d0
5271             param( 3) = -14.15261d0
5272             param( 4) =  -7.46589d0
5273             param( 5) =  17.94491d0
5274             param( 6) =   1.00000d0
5275             param( 7) =   3.77344d0
5276             param( 8) = -26.04463d0
5277             param( 9) =  30.69913d0
5278             param(10) =  -9.22695d0
5279             call nwxc_c_m05_d3(param,nwxc_rho_tol,ipol,nq,
5280     +            nwxc_wghts(it),rho,gamma,tau,f)
5281           case (NWXCP_C_M05_2X)
5282             param( 1) =   1.00000d0
5283             param( 2) =   1.09297d0
5284             param( 3) =  -3.79171d0
5285             param( 4) =   2.82810d0
5286             param( 5) = -10.58909d0
5287             param( 6) =   1.00000d0
5288             param( 7) =  -3.05430d0
5289             param( 8) =   7.61854d0
5290             param( 9) =   1.47665d0
5291             param(10) = -11.92365d0
5292             call nwxc_c_m05_d3(param,nwxc_rho_tol,ipol,nq,
5293     +            nwxc_wghts(it),rho,gamma,tau,f)
5294           case (NWXCP_C_M06)
5295
5296             param( 1) =  -2.741539D+00
5297             param( 2) =  -6.720113D-01
5298             param( 3) =  -7.932688D-02
5299             param( 4) =   1.918681D-03
5300             param( 5) =  -2.032902D-03
5301             param( 6) =   0.000000D+00
5302             param( 7) =   4.905945D-01
5303             param( 8) =  -1.437348D-01
5304             param( 9) =   2.357824D-01
5305             param(10) =   1.871015D-03
5306             param(11) =  -3.788963D-03
5307             param(12) =   0.000000D+00
5308c
5309             param(13) =   3.741539D+00
5310             param(14) =   2.187098D+02
5311             param(15) =  -4.531252D+02
5312             param(16) =   2.936479D+02
5313             param(17) =  -6.287470D+01
5314             param(18) =   5.094055D-01
5315             param(19) =  -1.491085D+00
5316             param(20) =   1.723922D+01
5317             param(21) =  -3.859018D+01
5318             param(22) =   2.845044D+01
5319c
5320             call nwxc_c_m06_d3(param,nwxc_rho_tol,ipol,nq,
5321     +            nwxc_wghts(it),rho,gamma,tau,f)
5322           case (NWXCP_C_M06_HF)
5323c
5324             param( 1) =  -6.746338D-01
5325             param( 2) =  -1.534002D-01
5326             param( 3) =  -9.021521D-02
5327             param( 4) =  -1.292037D-03
5328             param( 5) =  -2.352983D-04
5329             param( 6) =   0.000000D+00
5330             param( 7) =   8.976746D-01
5331             param( 8) =  -2.345830D-01
5332             param( 9) =   2.368173D-01
5333             param(10) =  -9.913890D-04
5334             param(11) =  -1.146165D-02
5335             param(12) =   0.000000D+00
5336c
5337             param(13) =   1.674634D+00
5338             param(14) =   5.732017D+01
5339             param(15) =   5.955416D+01
5340             param(16) =  -2.311007D+02
5341             param(17) =   1.255199D+02
5342             param(18) =   1.023254D-01
5343             param(19) =  -2.453783D+00
5344             param(20) =   2.913180D+01
5345             param(21) =  -3.494358D+01
5346             param(22) =   2.315955D+01
5347c
5348             call nwxc_c_m06_d3(param,nwxc_rho_tol,ipol,nq,
5349     +            nwxc_wghts(it),rho,gamma,tau,f)
5350           case (NWXCP_C_M06_L)
5351c
5352             param( 1) =   3.957626D-01
5353             param( 2) =  -5.614546D-01
5354             param( 3) =   1.403963D-02
5355             param( 4) =   9.831442D-04
5356             param( 5) =  -3.577176D-03
5357             param( 6) =   0.000000D+00
5358             param( 7) =   4.650534D-01
5359             param( 8) =   1.617589D-01
5360             param( 9) =   1.833657D-01
5361             param(10) =   4.692100D-04
5362             param(11) =  -4.990573D-03
5363             param(12) =   0.000000D+00
5364c
5365             param(13) =   6.042374D-01
5366             param(14) =   1.776783D+02
5367             param(15) =  -2.513252D+02
5368             param(16) =   7.635173D+01
5369             param(17) =  -1.255699D+01
5370             param(18) =   5.349466D-01
5371             param(19) =   5.396620D-01
5372             param(20) =  -3.161217D+01
5373             param(21) =   5.149592D+01
5374             param(22) =  -2.919613D+01
5375c
5376             call nwxc_c_m06_d3(param,nwxc_rho_tol,ipol,nq,
5377     +            nwxc_wghts(it),rho,gamma,tau,f)
5378           case (NWXCP_C_M06_2X)
5379c
5380             param( 1) =   1.166404D-01
5381             param( 2) =  -9.120847D-02
5382             param( 3) =  -6.726189D-02
5383             param( 4) =   6.720580D-05
5384             param( 5) =   8.448011D-04
5385             param( 6) =   0.000000D+00
5386             param( 7) =   6.902145D-01
5387             param( 8) =   9.847204D-02
5388             param( 9) =   2.214797D-01
5389             param(10) =  -1.968264D-03
5390             param(11) =  -6.775479D-03
5391             param(12) =   0.000000D+00
5392c
5393             param(13) =   8.833596D-01
5394             param(14) =   3.357972D+01
5395             param(15) =  -7.043548D+01
5396             param(16) =   4.978271D+01
5397             param(17) =  -1.852891D+01
5398             param(18) =   3.097855D-01
5399             param(19) =  -5.528642D+00
5400             param(20) =   1.347420D+01
5401             param(21) =  -3.213623D+01
5402             param(22) =   2.846742D+01
5403c
5404             call nwxc_c_m06_d3(param,nwxc_rho_tol,ipol,nq,
5405     +            nwxc_wghts(it),rho,gamma,tau,f)
5406           case (NWXCP_C_M08_HX)
5407c            parameters A
5408             param(1)  =    1.0000000D+00
5409             param(2)  =   -4.0661387D-01
5410             param(3)  =   -3.3232530D+00
5411             param(4)  =    1.5540980D+00
5412             param(5)  =    4.4248033D+01
5413             param(6)  =   -8.4351930D+01
5414             param(7)  =   -1.1955581D+02
5415             param(8)  =    3.9147081D+02
5416             param(9)  =    1.8363851D+02
5417             param(10) =   -6.3268223D+02
5418             param(11) =   -1.1297403D+02
5419             param(12) =    3.3629312D+02
5420c            parameters B
5421             param(13) =    1.3812334D+00
5422             param(14) =   -2.4683806D+00
5423             param(15) =   -1.1901501D+01
5424             param(16) =   -5.4112667D+01
5425             param(17) =    1.0055846D+01
5426             param(18) =    1.4800687D+02
5427             param(19) =    1.1561420D+02
5428             param(20) =    2.5591815D+02
5429             param(21) =    2.1320772D+02
5430             param(22) =   -4.8412067D+02
5431             param(23) =   -4.3430813D+02
5432             param(24) =    5.6627964D+01
5433             call nwxc_c_m11_d3(param,nwxc_rho_tol,ipol,nq,
5434     +            nwxc_wghts(it),rho,gamma,tau,f)
5435           case (NWXCP_C_M08_SO)
5436c            parameters A
5437             param(1)  =   1.0000000D+00
5438             param(2)  =   0.0000000D+00
5439             param(3)  =  -3.9980886D+00
5440             param(4)  =   1.2982340D+01
5441             param(5)  =   1.0117507D+02
5442             param(6)  =  -8.9541984D+01
5443             param(7)  =  -3.5640242D+02
5444             param(8)  =   2.0698803D+02
5445             param(9)  =   4.6037780D+02
5446             param(10) =  -2.4510559D+02
5447             param(11) = -1.9638425D+02
5448             param(12) =  1.1881459D+02
5449c            parameters B
5450             param(13) =   1.0000000D+00
5451             param(14) =  -4.4117403D+00
5452             param(15) =  -6.4128622D+00
5453             param(16) =   4.7583635D+01
5454             param(17) =   1.8630053D+02
5455             param(18) =  -1.2800784D+02
5456             param(19) =  -5.5385258D+02
5457             param(20) =   1.3873727D+02
5458             param(21) =   4.1646537D+02
5459             param(22) =  -2.6626577D+02
5460             param(23) =   5.6676300D+01
5461             param(24) =   3.1673746D+02
5462             call nwxc_c_m11_d3(param,nwxc_rho_tol,ipol,nq,
5463     +            nwxc_wghts(it),rho,gamma,tau,f)
5464           case (NWXCP_C_M11)
5465c            parameters A
5466             param(1)  =  1.0000000D+00
5467             param(2)  =  0.0000000D+00
5468             param(3)  = -3.8933250D+00
5469             param(4)  = -2.1688455D+00
5470             param(5)  =  9.3497200D+00
5471             param(6)  = -1.9845140D+01
5472             param(7)  =  2.3455253D+00
5473             param(8)  =  7.9246513D+01
5474             param(9)  =  9.6042757D+00
5475             param(10) = -6.7856719D+01
5476             param(11) = -9.1841067D+00
5477             param(12) =  0.0000000D+00
5478c            parameters B
5479             param(13) =  7.2239798D-01
5480             param(14) =  4.3730564D-01
5481             param(15) = -1.6088809D+01
5482             param(16) = -6.5542437D+01
5483             param(17) =  3.2057230D+01
5484             param(18) =  1.8617888D+02
5485             param(19) =  2.0483468D+01
5486             param(20) = -7.0853739D+01
5487             param(21) =  4.4483915D+01
5488             param(22) = -9.4484747D+01
5489             param(23) = -1.1459868D+02
5490             param(24) =  0.0000000D+00
5491             call nwxc_c_m11_d3(param,nwxc_rho_tol,ipol,nq,
5492     +            nwxc_wghts(it),rho,gamma,tau,f)
5493           case (NWXCP_C_M11_L)
5494c            parameters A
5495             param(1)  =  1.000000D+00
5496             param(2)  =  0.000000D+00
5497             param(3)  =  2.750880D+00
5498             param(4)  = -1.562287D+01
5499             param(5)  =  9.363381D+00
5500             param(6)  =  2.141024D+01
5501             param(7)  = -1.424975D+01
5502             param(8)  = -1.134712D+01
5503             param(9)  =  1.022365D+01
5504             param(10) =  0.000000D+00
5505             param(11) =  0.000000D+00
5506             param(12) =  0.000000D+00
5507c            parameters B
5508             param(13) =  1.000000D+00
5509             param(14) = -9.082060D+00
5510             param(15) =  6.134682D+00
5511             param(16) = -1.333216D+01
5512             param(17) = -1.464115D+01
5513             param(18) =  1.713143D+01
5514             param(19) =  2.480738D+00
5515             param(20) = -1.007036D+01
5516             param(21) = -1.117521D-01
5517             param(22) =  0.000000D+00
5518             param(23) =  0.000000D+00
5519             param(24) =  0.000000D+00
5520             call nwxc_c_m11_d3(param,nwxc_rho_tol,ipol,nq,
5521     +            nwxc_wghts(it),rho,gamma,tau,f)
5522          case (NWXCP_C_MPBE)
5523            param(1) = 0.066724550603149d0
5524            call nwxc_c_mpbe_d3(param,nwxc_rho_tol,ipol,nq,
5525     +           nwxc_wghts(it),rho,gamma,f)
5526           case (NWXCP_C_OP)
5527             param(1) = 2.3670d0
5528             call nwxc_c_op_d3(nwxc_k_becke88_d3,param,nwxc_rho_tol,
5529     +            ipol,nq,nwxc_wghts(it),rho,gamma,f)
5530          case (NWXCP_C_OPT)
5531            call nwxc_c_opt_d3(nwxc_rho_tol,ipol,nq,
5532     +           nwxc_wghts(it),rho,gamma,f)
5533           case (NWXCP_C_PW6B95)
5534             param(1) = 0.00262d0
5535             param(2) = 0.03668d0
5536             call nwxc_c_b95_d3(param,nwxc_rho_tol,ipol,nq,
5537     +                          nwxc_wghts(it),rho,gamma,tau,f)
5538           case (NWXCP_C_PWB6K)
5539             param(1) = 0.00353d0
5540             param(2) = 0.04120d0
5541             call nwxc_c_b95_d3(param,nwxc_rho_tol,ipol,nq,
5542     +                          nwxc_wghts(it),rho,gamma,tau,f)
5543          case (NWXCP_C_PW91LDA)
5544            call nwxc_c_pw91lda_d3(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
5545     +                             rho,f)
5546          case (NWXCP_C_LYP)
5547            call nwxc_c_lyp_d3(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
5548     +                         rho,gamma,f)
5549          case (NWXCP_C_PZ81)
5550            call nwxc_c_perdew81_d3(nwxc_rho_tol,ipol,nq,
5551     +                              nwxc_wghts(it),rho,f)
5552          case (NWXCP_C_P86)
5553            call nwxc_c_perdew86_d3(nwxc_rho_tol,ipol,nq,
5554     +                              nwxc_wghts(it),rho,gamma,f)
5555          case (NWXCP_C_P91)
5556            call nwxc_c_p91_d3(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
5557     +                         rho,gamma,f)
5558          case (NWXCP_C_P91_VWN5)
5559            call nwxc_c_p91_vwn5_d3(nwxc_rho_tol,ipol,nq,
5560     +                              nwxc_wghts(it),rho,gamma,f)
5561          case (NWXCP_C_PBE)
5562            param(1) = 0.066724550603149d0
5563            call nwxc_c_pbe_d3(param,nwxc_rho_tol,ipol,nq,
5564     +                         nwxc_wghts(it),rho,gamma,f)
5565          case (NWXCP_C_PBESOL)
5566            param(1) = 0.046d0
5567            call nwxc_c_pbe_d3(param,nwxc_rho_tol,ipol,nq,
5568     +                         nwxc_wghts(it),rho,gamma,f)
5569          case (NWXCP_C_PKZB)
5570            param(1) = 0.066724550603149d0
5571            call nwxc_c_pkzb99_d3(param,nwxc_rho_tol,ipol,nq,
5572     +                            nwxc_wghts(it),rho,gamma,tau,f)
5573          case (NWXCP_C_SPBE)
5574            call nwxc_c_spbe_d3(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
5575     +                          rho,gamma,f)
5576          case (NWXCP_C_SOGGA11)
5577            param(1)  =  5.00000d-01
5578            param(2)  = -4.62334D+00
5579            param(3)  =  8.00410D+00
5580            param(4)  = -130.226D+00
5581            param(5)  =  38.2685D+00
5582            param(6)  =  69.5599D+00
5583            param(7)  =  5.00000d-01
5584            param(8)  =  3.62334D+00
5585            param(9)  =  9.36393D+00
5586            param(10) =  34.5114D+00
5587            param(11) = -18.5684D+00
5588            param(12) = -0.16519D+00
5589            call nwxc_c_sogga_d3(param,nwxc_rho_tol,ipol,nq,
5590     +                           nwxc_wghts(it),rho,gamma,f)
5591          case (NWXCP_C_SOGGA11_X)
5592            param(1)  =  5.00000d-01
5593            param(2)  =  7.82439d+01
5594            param(3)  =  2.57211d+01
5595            param(4)  = -1.38830d+01
5596            param(5)  = -9.87375d+00
5597            param(6)  = -1.41357d+01
5598            param(7)  =  5.00000d-01
5599            param(8)  = -7.92439d+01
5600            param(9)  =  1.63725d+01
5601            param(10) =  2.08129d+00
5602            param(11) =  7.50769d+00
5603            param(12) = -1.01861d+01
5604            call nwxc_c_sogga_d3(param,nwxc_rho_tol,ipol,nq,
5605     +                           nwxc_wghts(it),rho,gamma,f)
5606          case (NWXCP_C_TPSS)
5607            param(1) = 0.066724550603149d0
5608            call nwxc_c_tpss03_d3(param,nwxc_rho_tol,ipol,nq,
5609     +                            nwxc_wghts(it),rho,gamma,tau,f)
5610          case (NWXCP_C_VS98)
5611            param(1)  =  7.035010d-01
5612            param(2)  =  7.694574d-03
5613            param(3)  =  5.152765d-02
5614            param(4)  =  3.394308d-05
5615            param(5)  = -1.269420d-03
5616            param(6)  =  1.296118d-03
5617            param(7)  =  3.270912d-01
5618            param(8)  = -3.228915d-02
5619            param(9)  = -2.942406d-02
5620            param(10) =  2.134222d-03
5621            param(11) = -5.451559d-03
5622            param(12) =  1.577575d-02
5623            call nwxc_c_vs98_d3(param,nwxc_rho_tol,ipol,nq,
5624     +           nwxc_wghts(it),rho,gamma,tau,f)
5625          case (NWXCP_C_VWN1)
5626            call nwxc_c_vwn1_d3(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
5627     +                          rho,f)
5628          case (NWXCP_C_VWN1_RPA)
5629            call nwxc_c_vwn1_rpa_d3(nwxc_rho_tol,ipol,nq,
5630     +                              nwxc_wghts(it),
5631     +                              rho,f)
5632          case (NWXCP_C_VWN2)
5633            call nwxc_c_vwn2_d3(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
5634     +                          rho,f)
5635          case (NWXCP_C_VWN3)
5636            call nwxc_c_vwn3_d3(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
5637     +                          rho,f)
5638          case (NWXCP_C_VWN4)
5639            call nwxc_c_vwn4_d3(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
5640     +                          rho,f)
5641          case (NWXCP_C_VWN5)
5642            call nwxc_c_vwn5_d3(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
5643     +                          rho,f)
5644          case (NWXCP_BOP)
5645            param(1) = 2.3670d0
5646            call nwxc_c_op_d3(nwxc_k_becke88_d3,param,nwxc_rho_tol,
5647     +           ipol,nq,nwxc_wghts(it),rho,gamma,f)
5648          case (NWXCP_KT1)
5649            call nwxc_xc_kt1_d3(nwxc_rho_tol,ipol,nq,nwxc_wghts(it),
5650     +                          rho,gamma,f)
5651          case (NWXCP_PBEOP)
5652            param(1) = 2.3789d0
5653            call nwxc_c_op_d3(nwxc_k_pbe96_d3,param,nwxc_rho_tol,
5654     +           ipol,nq,nwxc_wghts(it),rho,gamma,f)
5655          case (NWXCP_SOP)
5656            param(1) = 2.5654d0
5657            call nwxc_c_op_d3(nwxc_k_dirac_d3,param,nwxc_rho_tol,
5658     +           ipol,nq,nwxc_wghts(it),rho,gamma,f)
5659          case default
5660            if (nwxc_oroot) then
5661              write(*,*)"nwxc_eval_df3: invalid functional",
5662     +                  nwxc_ids(it)
5663            endif
5664            call nwxc_printP()
5665            call errquit("nwxc_eval_df3: invalid functional",
5666     +                   nwxc_ids(it),0)
5667        end select
5668      enddo
5669C
5670      end
5671C> @}
5672c $Id$
5673