1C> \ingroup nwint
2C> @{
3C>
4C> \brief Compute 1-electron Gaussian periodic kinetic energy
5C> integral derivatives
6C>
7C> See [1] for details.
8C>
9C> [1] JE Jaffe, AC Hess,
10C>     <i>"Gaussian basis density functional theory for systems
11C>     periodic in two or three dimensions: Energy and forces"</i>,
12C>    J.Chem.Phys. <b>105</b>, 10983-10998 (1996), DOI:
13C>    <a href="https://doi.org/10.1063/1.472866">
14C>    10.1063/1.472866</a>
15C>
16      subroutine intpd_1eke(i_basis,ish,j_basis,jsh,R,lscr,scr,
17     &    lKea,Kea,idatom)
18*
19* $Id$
20*
21      implicit none
22#include "stdio.fh"
23#include "errquit.fh"
24#include "nwc_const.fh"
25#include "basP.fh"
26#include "basdeclsP.fh"
27#include "geomP.fh"
28#include "geobasmapP.fh"
29#include "mafdecls.fh"
30#include "bas_exndcf_dec.fh"
31#include "bas_ibs_dec.fh"
32#include "int_nbf.fh"
33c::external subroutines used
34c... errquit
35c::functions
36      logical cando_nw_1e
37      logical cando_nw
38      logical int_chk_init
39      logical int_chk_sh
40      external int_chk_init
41      external int_chk_sh
42      external cando_nw_1e
43      external cando_nw
44      integer int_nint_cart
45      external int_nint_cart
46c::passed
47      integer i_basis           !< [Input] basis set handle for ish functions
48      integer j_basis           !< [Input] basis set handle for jsh functions
49      integer ish               !< [Input] lexical contraction/shell index
50      integer jsh               !< [Input] lexical contraction/shell index
51      integer lscr              !< [Input] length of the scratch array
52      integer lKea              !< [Input] length of the integral array
53      double precision Kea(lKea) !< [Output] kinetic energy integral array
54      double precision scr(lscr) !< [Scratch] scratch array
55      double precision R(3)     !< [Input] translational vector fractional coordinates
56      integer idatom(*) !< [Output] array identifying centers for derivatives
57                        !< e.g.,
58                        !< - the first nint*3  derivatives go to center idatom(1)
59                        !< - the second nint*3 derivatives go to center idatom(2)
60c::local
61      logical shells_ok
62      integer i_geom, j_geom, ibas, jbas, ucont, mynint
63      integer Li, i_prim, i_gen, i_iexp, i_icfp, i_cent
64      integer Lj, j_prim, j_gen, j_iexp, j_icfp, j_cent
65      double precision xyz_new(3) ! new coordinates for jsh function center
66*rak:      integer jjj
67c
68      logical inline_chk_sh
69      integer WarnP
70      save WarnP
71      data WarnP /0/
72c
73#include "bas_exndcf_sfn.fh"
74#include "bas_ibs_sfn.fh"
75c... statement function for int_chk_sh
76      inline_chk_sh(ibas,ish) =
77     $    ((ish.gt.0) .and. (ish.le.ncont_tot_gb(ibas)))
78c
79c check initialization and shells
80c
81      if (.not.int_chk_init('intpd_1eke'))
82     &    call errquit('intpd_1eke: int_init was not called' ,0,
83     &                INT_ERR)
84c
85      ibas = i_basis + BASIS_HANDLE_OFFSET
86      jbas = j_basis + BASIS_HANDLE_OFFSET
87c
88      shells_ok = inline_chk_sh(ibas,ish)
89      shells_ok = shells_ok .and. inline_chk_sh(jbas,jsh)
90      if (.not.shells_ok)
91     &    call errquit('intpd_1eke: invalid contraction/shell',0,
92     &               BASIS_ERR)
93c
94      ucont   = (sf_ibs_cn2ucn(ish,ibas))
95      Li      = infbs_cont(CONT_TYPE ,ucont,ibas)
96      i_prim  = infbs_cont(CONT_NPRIM,ucont,ibas)
97      i_gen   = infbs_cont(CONT_NGEN ,ucont,ibas)
98      i_iexp  = infbs_cont(CONT_IEXP ,ucont,ibas)
99      i_icfp  = infbs_cont(CONT_ICFP ,ucont,ibas)
100      i_cent  = (sf_ibs_cn2ce(ish,ibas))
101      i_geom  = ibs_geom(ibas)
102c
103      ucont   = (sf_ibs_cn2ucn(jsh,jbas))
104      Lj      = infbs_cont(CONT_TYPE ,ucont,jbas)
105      j_prim  = infbs_cont(CONT_NPRIM,ucont,jbas)
106      j_gen   = infbs_cont(CONT_NGEN ,ucont,jbas)
107      j_iexp  = infbs_cont(CONT_IEXP ,ucont,jbas)
108      j_icfp  = infbs_cont(CONT_ICFP ,ucont,jbas)
109      j_cent  = (sf_ibs_cn2ce(jsh,jbas))
110      j_geom  = ibs_geom(jbas)
111c
112      mynint = int_nint_cart(i_basis,ish,j_basis,jsh,0,0,0,0)
113      if (i_cent.eq.j_cent) then
114*        write(luout,*)' automatic zero '
115        call ifill(2,0,idatom,1)
116        call dcopy((mynint*3*2),0.0d00,0,Kea,1)
117        return
118      endif
119      idatom(1) = i_cent
120      idatom(2) = j_cent
121c
122      if (i_geom.ne.j_geom.and.WarnP.eq.0) then
123        write(luout,*)
124     &      'intpd_1eke: WARNING: possible geometry inconsistency'
125        write(luout,*)'i_basis geometry handle:',i_geom
126        write(luout,*)'j_basis geometry handle:',j_geom
127        WarnP = 1
128      endif
129c
130c.. translate coordinates based on R
131      call intp_txyz(j_cent,j_geom,R,xyz_new)
132c
133      if (cando_nw(i_basis,ish,0).and.cando_nw(j_basis,jsh,0)) then
134        call hf1d(
135     &      coords(1,i_cent,i_geom),dbl_mb(mb_exndcf(i_iexp,ibas)),
136     &      dbl_mb(mb_exndcf(i_icfp,ibas)), i_prim, i_gen, Li, i_cent,
137     &      xyz_new,dbl_mb(mb_exndcf(j_iexp,jbas)),
138     &      dbl_mb(mb_exndcf(j_icfp,jbas)), j_prim, j_gen, Lj, j_cent,
139     &      coords(1,1,i_geom),charge(1,i_geom),
140     &      geom_invnucexp(1,i_geom),ncenter(i_geom),
141c.............................. doS    doT     doV     canonical
142     &      scr,Kea,scr,mynint,.false.,.true.,.false.,.false.,
143c........... dryrun
144     &      .false.,scr,lscr)
145        if (bas_spherical(ibas).or.bas_spherical(jbas)) then
146          if (Li.eq.-1) i_gen = 1
147          if (Lj.eq.-1) j_gen = 1
148          call spcart_2cBtran(Kea,scr,lscr,
149     &        int_nbf_x(Li),int_nbf_s(Li),Li,i_gen,bas_spherical(ibas),
150     &        int_nbf_x(Lj),int_nbf_s(Lj),Lj,j_gen,bas_spherical(jbas),
151     &        (3*2),.false.)
152        endif
153      else
154        call errquit('intpd_1eke: could not do sp or nw integrals',0,
155     &              INT_ERR)
156      endif
157c
158      end
159C> @}
160