!----------------------------------------------------------------- ! SUBROUTINE: mpot ! ! package : li3 Potentials ! ! Language : Fortran 77 ! ! author : V. Venturi (vanessa.venturi@nist.gov) ! ! revision : F. Colavecchia (flavioc@lanl.gov) ! ! purpose : Get the potential of the singlet and triplet Li2, ! once the data and PARAMETERs are read at syspot3; ! according to eq. (8) of JCP 118 5484 (2003). ! ! input : np -> degree of polynomial used in the akima interpolation. ! ndata -> number of ab initio+rkr+exchange data points ! rdata -> distance in a.u. for each data point ! vdata -> potentials at each data point. ! c6 -> data for Van der Waals form, eq. (3) ! c8 -> data for Van der Waals form, eq. (3) ! c10 -> data for Van der Waals form, eq. (3) ! cA -> data for exchange form, eq. (6) ! beta -> data for exchange form, eq. (6) ! gamma -> data for exchange form, eq. (6) ! a -> data for short range form, eq. (7) ! b -> data for short range form, eq. (7) ! nv -> singlet (nv=1) or triplet (nv=2) potential ! r -> internuclear distance in a.u. ! ! output : v -> li2 potential in a.u. ! ! ! notes : The original code included RKR data from table 3 ! (Linton et al J. Mol. Spect. 196, 20 (1999)). ! Now we make use of new RKR data provided by A. Ross ! (ross@in2p3.fr), read from rkr.dat. See also ! readme_li2.txt for the values of De, Do, a, rmin. ! Comments noted by CFC were included by F. Colavecchia ! !------------------------------------------------------------------- SUBROUTINE mpot (np, ndata, rdata, vdata, c6, c8, c10, CA, beta, & gamma, a, b, nv, r, v) USE Numeric_Kinds_Module ! REAL(KIND=WP_Kind) rdata, vdata, c6, c8, c10, CA, beta, gamma, a, b REAL(KIND=WP_Kind) r, v INTEGER :: np, ndata, nv DIMENSION rdata (ndata), vdata (ndata) ! ! ... Local Variables ! REAL(KIND=WP_Kind) vex, vdisp, rfinal rfinal = rdata (ndata) ! IF(r.ge.0.0d0 .and. r.lt.rdata(1) )THEN ! ! Extrapolate short range data using the form: aexp(-br) ! v = a * exp ( - b * r) ELSEIF (r.ge.rdata (1) .and.r.lt.rfinal)THEN ! ! Interpolate short range data ! CALL akimasv(np, ndata, rdata, vdata, 1, r, v) v = v / r**6 ELSEIF (r.ge.rfinal)THEN ! ! Calculate long range form ! IF(r<1.d+20)THEN vex = CA * exp ( - beta * r) * r**gamma vdisp = - c6 / r**6 - c8 / r**8 - c10 / r**10 ELSE vex=0.d0 vdisp=0.d0 ENDIF IF(nv.eq.1)THEN v = vdisp - vex ELSEIF (nv.eq.2)THEN v = vdisp + vex ENDIF ENDIF ! RETURN END SUBROUTINE mpot