1c $Id$
2*
3C> \ingroup nwint
4C> @{
5C>
6C> \brief Private wrapper routine that calls McMurchie-Davidson
7C> 1-electron integral routines
8C>
9C> Call the McMurchie-Davidson 1-electron integral routines and
10C> handle any permutations to compute the SP integrals.
11C>
12c:tex-% part of the internal API routines.
13c:tex-\subsection{int\_hf1sp}
14c:tex-This is a layer routine that calls the
15c:tex-McMurchie-Davidson one electron routine.  This layer
16c:tex-routine handles all permutations to compute sp integrals.
17c:tex-This routine should never be called by an application module.
18c:tex-
19c:tex-{\it Syntax:}
20c:tex-\begin{verbatim}
21      subroutine int_hf1sp(
22     &       xyzi,expi,coefi, i_nprim, i_ngen, Li, ictri,
23     &       xyzj,expj,coefj, j_nprim, j_ngen, Lj, ictrj,
24     &       xyz,zan,exinv,nat,S,T,V,lstv,doS,doT,doV,canAB,
25     &       dryrun,scr,lscr,msg)
26c:tex-\end{verbatim}
27      implicit none
28#include "apiP.fh"
29#include "errquit.fh"
30#include "stdio.fh"
31#include "nwc_const.fh"
32#include "int_nbf.fh"
33#include "util.fh"
34c::passed
35c:tex-For an integral $<i|Operator|j>$
36c:tex-\begin{verbatim}
37      integer i_nprim  !< [Input] num. prims on function i
38      integer i_ngen   !< [Input] num general conts on func. i
39      integer Li       !< [Input] angular momentum of func. i
40      integer ictri    !< [Input] lexical atom index for function i
41      integer j_nprim  !< [Input] num. prims on function j
42      integer j_ngen   !< [Input] num general conts on func. j
43      integer Lj       !< [Input] angular momentum of func. j
44      integer ictrj    !< [Input] lexical atom index for function j
45      integer nat      !< [Input] number of atoms
46      integer lscr     !< [Input] size of scratch array
47      integer lstv     !< [Input] size of any integral buffer
48      double precision xyzi(3)  !< [Input] position of center i
49      double precision expi(i_nprim) !< [Input] exponents on i
50      double precision coefi(i_nprim,i_ngen) !< [Input] i coeffs
51      double precision xyzj(3)  !< [Input] position of center j
52      double precision expj(j_nprim)  !< [Input] exponents on j
53      double precision coefj(j_nprim,j_ngen)  !< [Input] j coeffs
54      double precision xyz(3,nat)  !< [Input] all atom positions
55      double precision zan(nat)  !< [Input] charges on all atoms
56      double precision exinv(nat)   !< [Input] inverse nuclear exponents
57      double precision scr(lscr)  !< [Scratch] scratch buffers
58      double precision S(lstv)  !< [Output] overlap integrals
59      double precision T(lstv)  !< [Output] kinetic energy integrals
60      double precision V(lstv)  !< [Output] potential integrals
61      logical doS     !< [Input] compute overlap (True/False)
62      logical doT     !< [Input] compute kinetic (True/False)
63      logical doV     !< [Input] compute potential (True/False)
64      logical canAB   !< [Input] compute only canonical ints (false only)
65      logical dryrun  !< [Input] true means only compute required memory
66      character*(*) msg !< [Input] calling function identification message
67c:tex-\end{verbatim}
68c::local
69      integer offset
70      integer nintx, nint_xsp
71c
72*debug_print      integer iii
73c
74      if (Li.gt.-1.and.Lj.gt.-1) then
75        call int_hf1sp_ecp(
76     &         xyzi,expi,coefi,i_nprim,i_ngen,Li,ictri,
77     &         xyzj,expj,coefj,j_nprim,j_ngen,Lj,ictrj,
78     &         xyz,zan,exinv,nat,S,T,V,lstv,doS,doT,doV,canAB,
79     &         dryrun,scr,lscr,msg)
80c
81      elseif (Li.eq.-1.and.Lj.eq.-1) then
82c.............................................................. (SP|SP)
83c________________________________ (S|S)
84        call int_hf1sp_ecp(
85     &         xyzi,expi,coefi,i_nprim,1,0,ictri,
86     &         xyzj,expj,coefj,j_nprim,1,0,ictrj,
87     &         xyz,zan,exinv,nat,S,T,V,lstv,doS,doT,doV,canAB,
88     &         dryrun,scr,lscr,msg)
89c________________________________ (S|P)
90        offset = 1
91        call int_hf1sp_ecp(
92     &         xyzi,
93     &         expi,coefi(1,1),
94     &         i_nprim,1,0,ictri,
95     &         xyzj,
96     &         expj,coefj(1,2),
97     &         j_nprim,1,1,ictrj,
98     &         xyz,zan,exinv,nat,
99     &         S(offset+1),T(offset+1),V(offset+1),
100     &         (lstv-offset)
101     &         ,doS,doT,doV,canAB,
102     &         dryrun,scr,lscr,msg)
103c________________________________ (P|S)
104        offset = 1 + 3
105        call int_hf1sp_ecp(
106     &         xyzi,
107     &         expi,coefi(1,2),
108     &         i_nprim,1,1,ictri,
109     &         xyzj,
110     &         expj,coefj(1,1),
111     &         j_nprim,1,0,ictrj,
112     &         xyz,zan,exinv,nat,
113     &         S(offset+1),T(offset+1),V(offset+1),
114     &         (lstv-offset)
115     &         ,doS,doT,doV,canAB,
116     &         dryrun,scr,lscr,msg)
117c________________________________ (P|P)
118        offset = 1 + 3 + 3
119        call int_hf1sp_ecp(
120     &         xyzi,
121     &         expi,coefi(1,2),
122     &         i_nprim,1,1,ictri,
123     &         xyzj,
124     &         expj,coefj(1,2),
125     &         j_nprim,1,1,ictrj,
126     &         xyz,zan,exinv,nat,
127     &         S(offset+1),T(offset+1),V(offset+1),
128     &         (lstv-offset)
129     &         ,doS,doT,doV,canAB,
130     &         dryrun,scr,lscr,msg)
131*
132        if (doS) call int_1spsp(S,1)
133        if (doT) call int_1spsp(T,1)
134        if (dov) call int_1spsp(V,1)
135      elseif (Li.eq.-1) then
136c.............................................................. (SP|X)
137c________________________________ (S|X)
138        call int_hf1sp_ecp(
139     &         xyzi,expi,coefi,i_nprim,1,0,ictri,
140     &         xyzj,expj,coefj,j_nprim,j_ngen,Lj,ictrj,
141     &         xyz,zan,exinv,nat,S,T,V,lstv,doS,doT,doV,canAB,
142     &         dryrun,scr,lscr,msg)
143c________________________________ (P|X)
144        offset = 1*(Lj+1)*(Lj+2)/2*j_ngen
145        call int_hf1sp_ecp(
146     &         xyzi,
147     &         expi,coefi(1,2),
148     &         i_nprim,1,1,ictri,
149     &         xyzj,
150     &         expj,coefj,j_nprim,j_ngen,Lj,ictrj,
151     &         xyz,zan,exinv,nat,
152     &         S(offset+1),T(offset+1),V(offset+1),
153     &         (lstv-offset)
154     &         ,doS,doT,doV,canAB,
155     &         dryrun,scr,lscr,msg)
156      elseif (Lj.eq.-1) then
157c.............................................................. (X|SP)
158c________________________________ (X|S)
159        call int_hf1sp_ecp(
160     &         xyzi,expi,coefi,i_nprim,i_ngen,Li,ictri,
161     &         xyzj,expj,coefj,j_nprim,1,0,ictrj,
162     &         xyz,zan,exinv,nat,S,T,V,lstv,doS,doT,doV,canAB,
163     &         dryrun,scr,lscr,msg)
164c________________________________ (X|P)
165        offset = 1*(Li+1)*(Li+2)/2*i_ngen
166        call int_hf1sp_ecp(
167     &         xyzi,
168     &         expi,coefi,i_nprim,i_ngen,Li,ictri,
169     &         xyzj,
170     &         expj,coefj(1,2),
171     &         j_nprim,1,1,ictrj,
172     &         xyz,zan,exinv,nat,
173     &         S(offset+1),T(offset+1),V(offset+1),
174     &         (lstv-offset)
175     &         ,doS,doT,doV,canAB,
176     &         dryrun,scr,lscr,msg)
177c
178        if (li.eq.0.and.i_ngen.eq.1) then
179c * for i_ngen = 1
180c * nothing needed since (s|s), (s|p) is same order as (s|sp)
181c * (s|s), (s|x), (s|y), (s|z)
182          continue
183        else if (li.eq.1.and.i_ngen.eq.1) then
184          if (doS) call int_1psp(S,1)
185          if (doT) call int_1psp(T,1)
186          if (doV) call int_1psp(V,1)
187        else if (li.eq.2.and.i_ngen.eq.1) then
188          if (doS) call int_1dsp(S,1)
189          if (doT) call int_1dsp(T,1)
190          if (doV) call int_1dsp(V,1)
191        else
192          nintx   = (Li+1)*(Li+2)/2*i_ngen  ! size of X
193          nint_xsp = nintx * 4              ! size of X * size of sp
194          if (doS) then
195            call dcopy(nint_xsp,S,1,scr,1)
196            call int_sp1b(S,scr,scr(nintx+1),nintx,1)
197          endif
198          if (doT) then
199            call dcopy(nint_xsp,T,1,scr,1)
200            call int_sp1b(T,scr,scr(nintx+1),nintx,1)
201          endif
202          if (doV) then
203            call dcopy(nint_xsp,V,1,scr,1)
204            call int_sp1b(V,scr,scr(nintx+1),nintx,1)
205          endif
206        endif
207      else
208        write(luout,*)'int_hf1sp called by ',msg
209        call errquit('int_hf1sp: unknown case finished',911, INT_ERR)
210      endif
211c
212c
213      end
214C>
215C> \brief Call the McMurchie-Davidson 1-electron integral routines
216C> while handling all ECP integral options.
217C>
218c:tex-% part of the internal API routines.
219c:tex-\subsection{int\_hf1sp\_ecp}
220c:tex-This is a layer routine that calls the
221c:tex-McMurchie-Davidson one electron routine.  This layer
222c:tex-routine handles all options for computing ecp integrals.
223c:tex-This routine should never be called by an application module.
224c:tex-
225c:tex-{\it Syntax:}
226c:tex-\begin{verbatim}
227      subroutine int_hf1sp_ecp(
228     &       xyzi,expi,coefi, i_nprim, i_ngen, Li, ictri,
229     &       xyzj,expj,coefj, j_nprim, j_ngen, Lj, ictrj,
230     &       xyz,zan,exinv,nat,S,T,V,lstv,doS,doT,doV,canAB,
231     &       dryrun,scr,lscr,msg)
232c:tex-\end{verbatim}
233      implicit none
234#include "apiP.fh"
235#include "errquit.fh"
236#include "stdio.fh"
237#include "nwc_const.fh"
238#include "int_nbf.fh"
239#include "util.fh"
240c::passed
241c:tex-For an integral $<i|Operator|j>$
242c:tex-\begin{verbatim}
243      integer i_nprim  !< [Input] num. prims on function i
244      integer i_ngen   !< [Input] num general conts on func. i
245      integer Li       !< [Input] angular momentum of func. i
246      integer ictri    !< [Input] lexical atom index for function i
247      integer j_nprim  !< [Input] num. prims on function j
248      integer j_ngen   !< [Input] num general conts on func. j
249      integer Lj       !< [Input] angular momentum of func. j
250      integer ictrj    !< [Input] lexical atom index for function j
251      integer nat      !< [Input] number of atoms
252      integer lscr     !< [Input] size of scratch array
253      integer lstv     !< [Input] size of any integral buffer
254      double precision xyzi(3)  !< [Input] position of center i
255      double precision expi(i_nprim) !< [Input] exponents on i
256      double precision coefi(i_nprim,i_ngen) !< [Input] i coeffs
257      double precision xyzj(3)  !< [Input] position of center j
258      double precision expj(j_nprim)  !< [Input] exponents on j
259      double precision coefj(j_nprim,j_ngen)  !< [Input] j coeffs
260      double precision xyz(3,nat)  !< [Input] all atom positions
261      double precision zan(nat)  !< [Input] charges on all atoms
262      double precision exinv(nat)   !< [Input] inverse nuclear exponents
263      double precision scr(lscr)  !< [Scratch] scratch buffers
264      double precision S(lstv)  !< [Output] overlap integrals
265      double precision T(lstv)  !< [Output] kinetic energy integrals
266      double precision V(lstv)  !< [Output] potential integrals
267      logical doS     !< [Input] compute overlap (True/False)
268      logical doT     !< [Input] compute kinetic (True/False)
269      logical doV     !< [Input] compute potential (True/False)
270      logical canAB   !< [Input] compute only canonical ints (false only)
271      logical dryrun  !< [Input] true means only compute required memory
272      character*(*) msg !< [Input] calling func. identification message
273c:tex-\end{verbatim}
274c::local
275      integer nintV
276      integer offset
277*
278      call hf1(
279     &      xyzi,expi,coefi,i_nprim,i_ngen,Li,
280     &      xyzj,expj,coefj,j_nprim,j_ngen,Lj,
281     &      xyz,zan,exinv,nat,S,T,V,lstv,doS,doT,doV,canAB,
282     &      dryrun,scr,lscr)
283*
284      if (any_ecp.and.doV.and.msg.ne.'int_1eefc') then
285        nintV = int_nbf_x(Li)*i_ngen
286        nintV = nintV*int_nbf_x(Lj)*j_ngen
287        offset = nintV + 1
288*       write(luout,*)' lscr to ecp_hf1:',(lscr-nintV)
289        if (ictri.lt.0.or.ictrj.lt.0) then
290          write(luout,*)' int_hf1sp_ecp: ictri = ',ictri
291          write(luout,*)' int_hf1sp_ecp: ictrj = ',ictrj
292          write(luout,*)'int_hf1sp_ecp called by ',msg
293          call errquit(
294     &        'int_hf1sp: unknown center for ECPs',
295     &        911, INT_ERR)
296        endif
297c
298cc AJL/Begin/SPIN ECPs
299        if (msg.eq.'int_1epe_beta') then
300cc Call to spin polarised ecp calculation for Beta channel
301          call int_ecp_hf1_beta(
302     &         xyzi,expi,coefi,i_nprim,i_ngen,Li,ictri,
303     &         xyzj,expj,coefj,j_nprim,j_ngen,Lj,ictrj,
304     &         scr,nintV,scr(offset),(lscr-nintV),
305     &         dryrun)
306        else
307cc Original call to spin independent ECP
308          call int_ecp_hf1(
309     &         xyzi,expi,coefi,i_nprim,i_ngen,Li,ictri,
310     &         xyzj,expj,coefj,j_nprim,j_ngen,Lj,ictrj,
311     &         scr,nintV,scr(offset),(lscr-nintV),
312     &         dryrun)
313        endif
314cc AJL/End
315c
316*... sum ecp into V block
317        call daxpy(nintV, 1.0d00, scr,1,V,1)
318      endif
319*
320      end
321C>
322C> \brief Transform the S and P integrals to SP integrals
323C>
324C> This routine transforms integrals from the way they were
325C> computed \f$ (p|s) \f$ and \f$ (p|p) \f$ to \f$ (p|sp) \f$.
326C> The transformation is performed in place as follows:
327C>
328C> <table>
329C> <tr><th> no.</th><th>computed order</th><th>transformed order</th><th>permutation      </th></tr>
330C> <tr><td>  1 </td><td> \f$(x|s)\f$ </td><td> \f$(x|s)\f$ </td><td>                        </td></tr>
331C> <tr><td>  2 </td><td> \f$(y|s)\f$ </td><td> \f$(x|x)\f$ </td><td> \f$2 \rightarrow 5\f$  </td></tr>
332C> <tr><td>  3 </td><td> \f$(z|s)\f$ </td><td> \f$(x|y)\f$ </td><td> \f$3 \rightarrow 9\f$  </td></tr>
333C> <tr><td>  4 </td><td> \f$(x|x)\f$ </td><td> \f$(x|z)\f$ </td><td> \f$4 \rightarrow 2\f$  </td></tr>
334C> <tr><td>  5 </td><td> \f$(x|y)\f$ </td><td> \f$(y|s)\f$ </td><td> \f$5 \rightarrow 3\f$  </td></tr>
335C> <tr><td>  6 </td><td> \f$(x|z)\f$ </td><td> \f$(y|x)\f$ </td><td> \f$6 \rightarrow 4\f$  </td></tr>
336C> <tr><td>  7 </td><td> \f$(y|x)\f$ </td><td> \f$(y|y)\f$ </td><td> \f$7 \rightarrow 6\f$  </td></tr>
337C> <tr><td>  8 </td><td> \f$(y|y)\f$ </td><td> \f$(y|z)\f$ </td><td> \f$8 \rightarrow 7\f$  </td></tr>
338C> <tr><td>  9 </td><td> \f$(y|z)\f$ </td><td> \f$(z|s)\f$ </td><td> \f$9 \rightarrow 8\f$  </td></tr>
339C> <tr><td> 10 </td><td> \f$(z|x)\f$ </td><td> \f$(z|x)\f$ </td><td>                        </td></tr>
340C> <tr><td> 11 </td><td> \f$(z|y)\f$ </td><td> \f$(z|y)\f$ </td><td>                        </td></tr>
341C> <tr><td> 12 </td><td> \f$(z|z)\f$ </td><td> \f$(z|z)\f$ </td><td>                        </td></tr>
342C> </table>
343C>
344C>
345c:tex-% part of the internal API routines
346c:tex-\subsection{int\_1psp}
347c:tex-This routine transforms integrals from the way they
348c:tex-were computed $(p|s)$, $(p|p)$ to $(p|sp)$.
349c:tex-The transformation is done in place as follows:
350c:tex-\begin{tabular}{rccc}
351c:tex- & computed & transformed & \\
352c:tex- &  order   &   order     & \\
353c:tex-~1 & (x$|$s)  &  (x$|$s)  & \\
354c:tex-~2 & (y$|$s)  &  (x$|$x)  & 2 $\rightarrow$ 5\\
355c:tex-~3 & (z$|$s)  &  (x$|$y)  & 3 $\rightarrow$ 9\\
356c:tex-~4 & (x$|$x)  &  (x$|$z)  & 4 $\rightarrow$ 2\\
357c:tex-~5 & (x$|$y)  &  (y$|$s)  & 5 $\rightarrow$ 3\\
358c:tex-~6 & (x$|$z)  &  (y$|$x)  & 6 $\rightarrow$ 4\\
359c:tex-~7 & (y$|$x)  &  (y$|$y)  & 7 $\rightarrow$ 6\\
360c:tex-~8 & (y$|$y)  &  (y$|$z)  & 8 $\rightarrow$ 7\\
361c:tex-~9 & (y$|$z)  &  (z$|$s)  & 9 $\rightarrow$ 8\\
362c:tex-10 & (z$|$x)  &  (z$|$x)  &  \\
363c:tex-11 & (z$|$y)  &  (z$|$y)  &  \\
364c:tex-12 & (z$|$z)  &  (z$|$z)  &  \\
365c:tex-\end{tabular}
366c:tex-
367c:tex-{\it Syntax:}
368c:tex-\begin{verbatim}
369      subroutine int_1psp(block,num_blocks)
370c:tex-\end{verbatim}
371c
372c transforms a (p|sp) block to correct order in place
373c integrals in block were calculated (p|s),(p|p).
374c      computed transformed
375c       order     order
376c  1.  (x|s)     (x|s)
377c  2.  (y|s)     (x|x)     2 -> 5
378c  3.  (z|s)     (x|y)     3 -> 9
379c  4.  (x|x)     (x|z)     4 -> 2
380c  5.  (x|y)     (y|s)     5 -> 3
381c  6.  (x|z)     (y|x)     6 -> 4
382c  7.  (y|x)     (y|y)     7 -> 6
383c  8.  (y|y)     (y|z)     8 -> 7
384c  9.  (y|z)     (z|s)     9 -> 8
385c 10.  (z|x)     (z|x)
386c 11.  (z|y)     (z|y)
387c 12.  (z|z)     (z|z)
388c
389      implicit none
390c:tex-\begin{verbatim}
391      integer num_blocks  !< [Input] num. blocks to transform
392      double precision block(12,num_blocks) !< [Input/output] integral block
393c:tex-\end{verbatim}
394c
395      integer ib
396      double precision temp1, temp2
397      do 00100 ib = 1,num_blocks
398        temp1       = block(2,ib)  ! 2 -> temp1
399        temp2       = block(3,ib)  ! 3 -> temp2
400        block(2,ib) = block(4,ib)  ! 4 -> 2
401        block(3,ib) = block(5,ib)  ! 5 -> 3
402        block(4,ib) = block(6,ib)  ! 6 -> 4
403        block(6,ib) = block(7,ib)  ! 7 -> 6
404        block(7,ib) = block(8,ib)  ! 8 -> 7
405        block(8,ib) = block(9,ib)  ! 9 -> 8
406        block(9,ib) = temp2        ! temp2 -> 9 or 3 -> 9
407        block(5,ib) = temp1        ! temp1 -> 5 or 2 -> 5
40800100 continue
409      end
410C>
411C> \brief Transform integrals involving D functions to
412C> SP integrals
413C>
414C> Transform integrals from the way they were computed
415C> \f$(d|s)\f$ and \f$(d|p)\f$ to \f$(d|sp)\f$. The transformation
416C> proceeds in place.
417C>
418C> <table>
419C> <tr><th> no.</th><th>computed order</th><th>transformed order</th><th>permutation      </th></tr>
420C> <tr><td>  1 </td><td> \f$(xx|s)\f$  </td><td> \f$(xx|s)\f$     </td><td>                       </td></tr>
421C> <tr><td>  2 </td><td> \f$(xy|s)\f$  </td><td> \f$(xx|x)\f$     </td><td> \f$2 \rightarrow 5\f$ </td></tr>
422C> <tr><td>  3 </td><td> \f$(xz|s)\f$  </td><td> \f$(xx|y)\f$     </td><td> \f$3 \rightarrow 9\f$ </td></tr>
423C> <tr><td>  4 </td><td> \f$(yy|s)\f$  </td><td> \f$(xx|z)\f$     </td><td> \f$4 \rightarrow 13\f$ </td></tr>
424C> <tr><td>  5 </td><td> \f$(yz|s)\f$  </td><td> \f$(xy|s)\f$     </td><td> \f$5 \rightarrow 17\f$ </td></tr>
425C> <tr><td>  6 </td><td> \f$(zz|s)\f$  </td><td> \f$(xy|x)\f$     </td><td> \f$6 \rightarrow 21\f$ </td></tr>
426C> <tr><td>  7 </td><td> \f$(xx|x)\f$  </td><td> \f$(xy|y)\f$     </td><td> \f$7 \rightarrow 2\f$ </td></tr>
427C> <tr><td>  8 </td><td> \f$(xx|y)\f$  </td><td> \f$(xy|z)\f$     </td><td> \f$8 \rightarrow 3\f$ </td></tr>
428C> <tr><td>  9 </td><td> \f$(xx|z)\f$  </td><td> \f$(xz|s)\f$     </td><td> \f$9 \rightarrow 4\f$ </td></tr>
429C> <tr><td> 10 </td><td> \f$(xy|x)\f$  </td><td> \f$(xz|x)\f$     </td><td> \f$10\rightarrow 6\f$ </td></tr>
430C> <tr><td> 11 </td><td> \f$(xy|y)\f$  </td><td> \f$(xz|y)\f$     </td><td> \f$11\rightarrow 7\f$ </td></tr>
431C> <tr><td> 12 </td><td> \f$(xy|z)\f$  </td><td> \f$(xz|z)\f$     </td><td> \f$12\rightarrow 8\f$ </td></tr>
432C> <tr><td> 13 </td><td> \f$(xz|x)\f$  </td><td> \f$(yy|s)\f$     </td><td> \f$13\rightarrow 10\f$ </td></tr>
433C> <tr><td> 14 </td><td> \f$(xz|y)\f$  </td><td> \f$(yy|x)\f$     </td><td> \f$14\rightarrow 11\f$ </td></tr>
434C> <tr><td> 15 </td><td> \f$(xz|z)\f$  </td><td> \f$(yy|y)\f$     </td><td> \f$15\rightarrow 12\f$ </td></tr>
435C> <tr><td> 16 </td><td> \f$(yy|x)\f$  </td><td> \f$(yy|z)\f$     </td><td> \f$16\rightarrow 14\f$ </td></tr>
436C> <tr><td> 17 </td><td> \f$(yy|y)\f$  </td><td> \f$(yz|s)\f$     </td><td> \f$17\rightarrow 15\f$ </td></tr>
437C> <tr><td> 18 </td><td> \f$(yy|z)\f$  </td><td> \f$(yz|x)\f$     </td><td> \f$18\rightarrow 16\f$ </td></tr>
438C> <tr><td> 19 </td><td> \f$(yz|x)\f$  </td><td> \f$(yz|y)\f$     </td><td> \f$19\rightarrow 18\f$ </td></tr>
439C> <tr><td> 20 </td><td> \f$(yz|y)\f$  </td><td> \f$(yz|z)\f$     </td><td> \f$20\rightarrow 19\f$ </td></tr>
440C> <tr><td> 21 </td><td> \f$(yz|z)\f$  </td><td> \f$(zz|s)\f$     </td><td> \f$21\rightarrow 20\f$ </td></tr>
441C> <tr><td> 22 </td><td> \f$(zz|x)\f$  </td><td> \f$(zz|x)\f$     </td><td>                        </td></tr>
442C> <tr><td> 23 </td><td> \f$(zz|y)\f$  </td><td> \f$(zz|y)\f$     </td><td>                        </td></tr>
443C> <tr><td> 24 </td><td> \f$(zz|z)\f$  </td><td> \f$(zz|z)\f$     </td><td>                        </td></tr>
444C> </table>
445C>
446c:tex-% part of the internal API routines
447c:tex-\subsection{int\_1dsp}
448c:tex-This routine transforms integrals from the way they
449c:tex-were computed $(d|s)$, $(d|p)$ to $(d|sp)$.
450c:tex-The transformation is done in place as follows:
451c:tex-\begin{tabular}{rccc}
452c:tex-  &  computed  & transformed & \\
453c:tex-  &  ~order    &  order & \\
454c:tex-~1 & (xx$|$s)  &  (xx$|$s)  & \\
455c:tex-~2 & (xy$|$s)  &  (xx$|$x)  &  ~2 $\rightarrow$ 5~~ \\
456c:tex-~3 & (xz$|$s)  &  (xx$|$y)  &  ~3 $\rightarrow$ 9~~ \\
457c:tex-~4 & (yy$|$s)  &  (xx$|$z)  &  ~4 $\rightarrow$ 13~ \\
458c:tex-~5 & (yz$|$s)  &  (xy$|$s)  &  ~5 $\rightarrow$ 17~ \\
459c:tex-~6 & (zz$|$s)  &  (xy$|$x)  &  ~6 $\rightarrow$ 21~ \\
460c:tex-~7 & (xx$|$x)  &  (xy$|$y)  &  ~7 $\rightarrow$ 2~~ \\
461c:tex-~8 & (xx$|$y)  &  (xy$|$z)  &  ~8 $\rightarrow$ 3~~ \\
462c:tex-~9 & (xx$|$z)  &  (xz$|$s)  &  ~9 $\rightarrow$ 4~~ \\
463c:tex-10 & (xy$|$x)  &  (xz$|$x)  &  10 $\rightarrow$ 6~~ \\
464c:tex-11 & (xy$|$y)  &  (xz$|$y)  &  11 $\rightarrow$ 7~~ \\
465c:tex-12 & (xy$|$z)  &  (xz$|$z)  &  12 $\rightarrow$ 8~~ \\
466c:tex-13 & (xz$|$x)  &  (yy$|$s)  &  13 $\rightarrow$ 10~ \\
467c:tex-14 & (xz$|$y)  &  (yy$|$x)  &  14 $\rightarrow$ 11~ \\
468c:tex-15 & (xz$|$z)  &  (yy$|$y)  &  15 $\rightarrow$ 12~ \\
469c:tex-16 & (yy$|$x)  &  (yy$|$z)  &  16 $\rightarrow$ 14~ \\
470c:tex-17 & (yy$|$y)  &  (yz$|$s)  &  17 $\rightarrow$ 15~ \\
471c:tex-18 & (yy$|$z)  &  (yz$|$x)  &  18 $\rightarrow$ 16~ \\
472c:tex-19 & (yz$|$x)  &  (yz$|$y)  &  19 $\rightarrow$ 18~ \\
473c:tex-20 & (yz$|$y)  &  (yz$|$z)  &  20 $\rightarrow$ 19~ \\
474c:tex-21 & (yz$|$z)  &  (zz$|$s)  &  21 $\rightarrow$ 20~ \\
475c:tex-22 & (zz$|$x)  &  (zz$|$x)  & \\
476c:tex-23 & (zz$|$y)  &  (zz$|$y)  & \\
477c:tex-24 & (zz$|$z)  &  (zz$|$z)  & \\
478c:tex-\end{tabular}
479c:tex-
480c:tex-{\it Syntax:}
481c:tex-\begin{verbatim}
482      subroutine int_1dsp(block,num_blocks)
483c:tex-\end{verbatim}
484c
485c transforms a (d|sp) block to correct order in place
486c integrals in block were calculated (d|s),(d|p).
487c      computed transformed
488c       order     order
489c  1.  (xx|s)     (xx|s)
490c  2.  (xy|s)     (xx|x)  2 -> 5   *
491c  3.  (xz|s)     (xx|y)  3 -> 9   *
492c  4.  (yy|s)     (xx|z)  4 -> 13  *
493c  5.  (yz|s)     (xy|s)  5 -> 17  *
494c  6.  (zz|s)     (xy|x)  6 -> 21  *
495c  7.  (xx|x)     (xy|y)  7 -> 2   *
496c  8.  (xx|y)     (xy|z)  8 -> 3   *
497c  9.  (xx|z)     (xz|s)  9 -> 4   *
498c 10.  (xy|x)     (xz|x) 10 -> 6   *
499c 11.  (xy|y)     (xz|y) 11 -> 7   *
500c 12.  (xy|z)     (xz|z) 12 -> 8   *
501c 13.  (xz|x)     (yy|s) 13 -> 10  *
502c 14.  (xz|y)     (yy|x) 14 -> 11  *
503c 15.  (xz|z)     (yy|y) 15 -> 12  *
504c 16.  (yy|x)     (yy|z) 16 -> 14  *
505c 17.  (yy|y)     (yz|s) 17 -> 15  *
506c 18.  (yy|z)     (yz|x) 18 -> 16  *
507c 19.  (yz|x)     (yz|y) 19 -> 18  *
508c 20.  (yz|y)     (yz|z) 20 -> 19  *
509c 21.  (yz|z)     (zz|s) 21 -> 20  *
510c 22.  (zz|x)     (zz|x)
511c 23.  (zz|y)     (zz|y)
512c 24.  (zz|z)     (zz|z)
513c
514      implicit none
515c:tex-\begin{verbatim}
516      integer num_blocks  !< [Input] num. blocks to transform
517      double precision block(24,num_blocks) !< [Input/Output] integral block
518c:tex-\end{verbatim}
519c
520      double precision temp1, temp2, temp3
521      integer ib
522c
523      do 00100 ib = 1, num_blocks
524        temp1        = block(2,ib)    ! 2 -> temp1
525        block(2,ib)  = block(7,ib)    ! 7 -> 2
526        temp2        = block(3,ib)    ! 3 -> temp2
527        block(3,ib)  = block(8,ib)    ! 8 -> 3
528        temp3        = block(4,ib)    ! 4 -> temp3
529        block(4,ib)  = block(9,ib)    ! 9 -> 4
530        block(9,ib)  = temp2          ! temp2 -> 9 or 3 -> 9
531        temp2        = block(6,ib)    ! 6 -> temp2
532        block(6,ib)  = block(10,ib)   ! 10 -> 6
533        block(7,ib)  = block(11,ib)   ! 11 -> 7
534        block(8,ib)  = block(12,ib)   ! 12 -> 8
535        block(10,ib) = block(13,ib)   ! 13 -> 10
536        block(11,ib) = block(14,ib)   ! 14 -> 11
537        block(12,ib) = block(15,ib)   ! 15 -> 12
538        block(14,ib) = block(16,ib)   ! 16 -> 14
539        block(15,ib) = block(17,ib)   ! 17 -> 15
540        block(17,ib) = block(5,ib)    ! 5 -> 17
541        block(5,ib)  = temp1          ! temp1 -> 5 or 2 -> 5
542        block(16,ib) = block(18,ib)   ! 18 -> 16
543        block(18,ib) = block(19,ib)   ! 19 -> 18
544        block(19,ib) = block(20,ib)   ! 20 -> 19
545        block(20,ib) = block(21,ib)   ! 21 -> 20
546        block(13,ib) = temp3          ! temp3 -> 13 or 4 -> 13
547        block(21,ib) = temp2          ! temp2 -> 21 or 6 -> 21
54800100 continue
549      end
550C>
551C> \brief Transform the integrals from the way they were computed
552C> as \f$(s|s)\f$, \f$(s|p)\f$, \f$(p|s)\f$ and \f$(p|p)\f$ to
553C> \f$(sp|sp)\f$
554C>
555C> This routine transforms the integrals from the way they were computed
556C> as \f$(s|s)\f$, \f$(s|p)\f$, \f$(p|s)\f$ and \f$(p|p)\f$ to
557C> \f$(sp|sp)\f$. The transformation completes as follows:
558C>
559C> <table>
560C> <tr><th> no.</th><th>computed order</th><th>transformed order</th><th>permutation      </th></tr>
561C> <tr><td>  1 </td><td> \f$(s|s)\f$ </td><td> \f$(s|s)\f$ </td><td>                        </td></tr>
562C> <tr><td>  2 </td><td> \f$(s|x)\f$ </td><td> \f$(s|x)\f$ </td><td>                        </td></tr>
563C> <tr><td>  3 </td><td> \f$(s|y)\f$ </td><td> \f$(s|y)\f$ </td><td>                        </td></tr>
564C> <tr><td>  4 </td><td> \f$(s|z)\f$ </td><td> \f$(s|z)\f$ </td><td>                        </td></tr>
565C> <tr><td>  5 </td><td> \f$(x|s)\f$ </td><td> \f$(x|s)\f$ </td><td>                        </td></tr>
566C> <tr><td>  6 </td><td> \f$(y|s)\f$ </td><td> \f$(x|x)\f$ </td><td> \f$6 \rightarrow 9 \f$ </td></tr>
567C> <tr><td>  7 </td><td> \f$(z|s)\f$ </td><td> \f$(x|y)\f$ </td><td> \f$7 \rightarrow 13\f$ </td></tr>
568C> <tr><td>  8 </td><td> \f$(x|x)\f$ </td><td> \f$(x|z)\f$ </td><td> \f$8 \rightarrow 6 \f$ </td></tr>
569C> <tr><td>  9 </td><td> \f$(x|y)\f$ </td><td> \f$(y|s)\f$ </td><td> \f$9 \rightarrow 7 \f$ </td></tr>
570C> <tr><td> 10 </td><td> \f$(x|z)\f$ </td><td> \f$(y|x)\f$ </td><td> \f$10\rightarrow 8 \f$ </td></tr>
571C> <tr><td> 11 </td><td> \f$(y|x)\f$ </td><td> \f$(y|y)\f$ </td><td> \f$11\rightarrow 10\f$ </td></tr>
572C> <tr><td> 12 </td><td> \f$(y|y)\f$ </td><td> \f$(y|z)\f$ </td><td> \f$12\rightarrow 11\f$ </td></tr>
573C> <tr><td> 13 </td><td> \f$(y|z)\f$ </td><td> \f$(z|s)\f$ </td><td> \f$13\rightarrow 12\f$ </td></tr>
574C> <tr><td> 14 </td><td> \f$(z|x)\f$ </td><td> \f$(z|x)\f$ </td><td>                        </td></tr>
575C> <tr><td> 15 </td><td> \f$(z|y)\f$ </td><td> \f$(z|y)\f$ </td><td>                        </td></tr>
576C> <tr><td> 16 </td><td> \f$(z|z)\f$ </td><td> \f$(z|z)\f$ </td><td>                        </td></tr>
577C> </table>
578C>
579c:tex-% part of the internal API routines
580c:tex-\subsection{int\_1spsp}
581c:tex-This routine transforms integrals from the way they
582c:tex-were computed $(s|s)$, $(s|p)$, $(p|s)$, $(p|p)$
583c:tex-to $(sp|sp)$.
584c:tex-The transformation is done in place as follows:
585c:tex-\begin{tabular}{rccc}
586c:tex-  &  computed & transformed   &   \\
587c:tex-  &   order   &  order  &   \\
588c:tex-~1 & (s$|$s)  &  (s$|$s)  &   \\
589c:tex-~2 & (s$|$x)  &  (s$|$x)  &   \\
590c:tex-~3 & (s$|$y)  &  (s$|$y)  &   \\
591c:tex-~4 & (s$|$z)  &  (s$|$z)  &   \\
592c:tex-~5 & (x$|$s)  &  (x$|$s)  &   \\
593c:tex-~6 & (y$|$s)  &  (x$|$x)  &  ~6 $\rightarrow$ 9\\
594c:tex-~7 & (z$|$s)  &  (x$|$y)  &  ~7 $\rightarrow$ 13\\
595c:tex-~8 & (x$|$x)  &  (x$|$z)  &  ~8 $\rightarrow$ 6\\
596c:tex-~9 & (x$|$y)  &  (y$|$s)  &  ~9 $\rightarrow$ 7\\
597c:tex-10 & (x$|$z)  &  (y$|$x)  &  10 $\rightarrow$ 8 \\
598c:tex-11 & (y$|$x)  &  (y$|$y)  &  11 $\rightarrow$ 10\\
599c:tex-12 & (y$|$y)  &  (y$|$z)  &  12 $\rightarrow$ 11\\
600c:tex-13 & (y$|$z)  &  (z$|$s)  &  13 $\rightarrow$ 12\\
601c:tex-14 & (z$|$x)  &  (z$|$x)  &   \\
602c:tex-15 & (z$|$y)  &  (z$|$y)  &   \\
603c:tex-16 & (z$|$z)  &  (z$|$z)  &   \\
604c:tex-\end{tabular}
605c:tex-
606c:tex-{\it Syntax:}
607c:tex-\begin{verbatim}
608      subroutine int_1spsp(block,num_blocks)
609c:tex-\end{verbatim}
610c
611c transforms a 1 electron integral block holding the 16
612c (sp|sp) integrals calculated from 4 calls:
613c           (s|s),(s|p),(p|s),(p|p) to the (sp|sp) order
614c
615c      computed transformed
616c       order      order
617c  1.   (s|s)      (s|s)
618c  2.   (s|x)      (s|x)
619c  3.   (s|y)      (s|y)
620c  4.   (s|z)      (s|z)
621c  5.   (x|s)      (x|s)
622c  6.   (y|s)      (x|x)   6 -> 9
623c  7.   (z|s)      (x|y)   7 -> 13
624c  8.   (x|x)      (x|z)   8 -> 6
625c  9.   (x|y)      (y|s)   9 -> 7
626c 10.   (x|z)      (y|x)  10 -> 8
627c 11.   (y|x)      (y|y)  11 -> 10
628c 12.   (y|y)      (y|z)  12 -> 11
629c 13.   (y|z)      (z|s)  13 -> 12
630c 14.   (z|x)      (z|x)
631c 15.   (z|y)      (z|y)
632c 16.   (z|z)      (z|z)
633      implicit none
634c:tex-\begin{verbatim}
635      integer num_blocks        !< [Input] num. blocks to transform
636      double precision block(16,num_blocks) !< [Input/Output] integral block
637c:tex-\end{verbatim}
638c
639      double precision temp
640      integer ib
641c
642      do 00100 ib = 1,num_blocks
643        temp         = block(6, ib)
644        block(6, ib) = block(8, ib)
645        block(8, ib) = block(10,ib)
646        block(10,ib) = block(11,ib)
647        block(11,ib) = block(12,ib)
648        block(12,ib) = block(13,ib)
649        block(13,ib) = block(7, ib)
650        block(7, ib) = block(9, ib)
651        block(9, ib) = temp
65200100 continue
653      end
654C>
655C> \brief Transform the integrals from the way they were computed as
656C> \f$(s|X)\f$ and \f$(p|X)\f$ to \f$(sp|X)\f$
657C>
658c:tex-% part of the internal API routines
659c:tex-\subsection{int\_1spa}
660c:tex-This routine transforms integrals from the way they
661c:tex-were computed $(s|X)$, $(p|X)$, to $(sp|X)$.
662c:tex-The transformation is {\bf NOT} done in place:
663c:tex-{\it Syntax:}
664c:tex-\begin{verbatim}
665      subroutine int_sp1a(sp_block,s_block,p_block,sizeb,num_blocks)
666c:tex-\end{verbatim}
667c
668*..  sp 1 electron transformation routine
669*.. (ash|bsh) block of integrals where a is an sp shell
670c
671      implicit none
672c::passed
673c:tex-\begin{verbatim}
674      integer sizeb  !< [Input] size of non sp block
675      integer num_blocks !< [Input] num of blocks to transform
676*
677      double precision sp_block(sizeb,1:4,num_blocks) !< [Output] (sp|X) transformed integral block
678*
679      double precision s_block(sizeb,num_blocks)      !< [Input] computed (s|X) block
680*
681      double precision p_block(sizeb,2:4,num_blocks)  !< [Input] computed (p|X) block
682c:tex-\end{verbatim}
683c::local
684      integer block
685      integer ib
686c
687      do 00100 block=1,num_blocks
688        do 00200 ib = 1,sizeb
689          sp_block(ib,1,block) = s_block(ib,block)
690          sp_block(ib,2,block) = p_block(ib,2,block)
691          sp_block(ib,3,block) = p_block(ib,3,block)
692          sp_block(ib,4,block) = p_block(ib,4,block)
69300200   continue
69400100 continue
695      end
696C>
697C> \brief Transform the integrals from the way they were computed as
698C> \f$(X|s)\f$ and \f$(X|p)\f$ to \f$(X|sp)\f$
699C>
700c:tex-% part of the internal API routines
701c:tex-\subsection{int\_sp1b}
702c:tex-This routine transforms integrals from the way they
703c:tex-were computed $(X|s)$, $(X|p)$, to $(X|sp)$.
704c:tex-The transformation is {\bf NOT} done in place:
705c:tex-{\it Syntax:}
706c:tex-\begin{verbatim}
707      subroutine int_sp1b(sp_block,s_block,p_block,sizea,num_blocks)
708c:tex-\end{verbatim}
709c
710*..  sp 1 electron transformation routine
711*.. (ash|bsh) block of integrals where b is an sp shell
712c
713      implicit none
714c::passed
715c:tex-\begin{verbatim}
716      integer sizea !< [Input] size of non sp block
717      integer num_blocks !< [Input] num of blocks to transform
718*
719      double precision sp_block(1:4,sizea,num_blocks) !< [Output] (X|sp) transformed integral block
720*
721      double precision s_block(sizea,num_blocks)      !< [Input] computed (X|s) block
722*
723      double precision p_block(2:4,sizea,num_blocks)  !< [Input] computed (X|p) block
724c:tex-\end{verbatim}
725c::local
726      integer block
727      integer ia
728c
729      do 00100 block = 1,num_blocks
730        do 00200 ia = 1,sizea
731
732          sp_block(1,ia,block) = s_block(ia,block)
733          sp_block(2,ia,block) = p_block(2,ia,block)
734          sp_block(3,ia,block) = p_block(3,ia,block)
735          sp_block(4,ia,block) = p_block(4,ia,block)
73600200   continue
73700100 continue
738      end
739C> @}
740