ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-4/src/UseTheForce/DarkSide/shapes.F90
Revision: 2756
Committed: Wed May 17 15:37:15 2006 UTC (18 years, 3 months ago) by gezelter
File size: 54497 byte(s)
Log Message:
Getting fortran side prepped for single precision...

File Contents

# User Rev Content
1 gezelter 1930 !!
2     !! Copyright (c) 2005 The University of Notre Dame. All Rights Reserved.
3     !!
4     !! The University of Notre Dame grants you ("Licensee") a
5     !! non-exclusive, royalty free, license to use, modify and
6     !! redistribute this software in source and binary code form, provided
7     !! that the following conditions are met:
8     !!
9     !! 1. Acknowledgement of the program authors must be made in any
10     !! publication of scientific results based in part on use of the
11     !! program. An acceptable form of acknowledgement is citation of
12     !! the article in which the program was described (Matthew
13     !! A. Meineke, Charles F. Vardeman II, Teng Lin, Christopher
14     !! J. Fennell and J. Daniel Gezelter, "OOPSE: An Object-Oriented
15     !! Parallel Simulation Engine for Molecular Dynamics,"
16     !! J. Comput. Chem. 26, pp. 252-271 (2005))
17     !!
18     !! 2. Redistributions of source code must retain the above copyright
19     !! notice, this list of conditions and the following disclaimer.
20     !!
21     !! 3. Redistributions in binary form must reproduce the above copyright
22     !! notice, this list of conditions and the following disclaimer in the
23     !! documentation and/or other materials provided with the
24     !! distribution.
25     !!
26     !! This software is provided "AS IS," without a warranty of any
27     !! kind. All express or implied conditions, representations and
28     !! warranties, including any implied warranty of merchantability,
29     !! fitness for a particular purpose or non-infringement, are hereby
30     !! excluded. The University of Notre Dame and its licensors shall not
31     !! be liable for any damages suffered by licensee as a result of
32     !! using, modifying or distributing the software or its
33     !! derivatives. In no event will the University of Notre Dame or its
34     !! licensors be liable for any lost revenue, profit or data, or for
35     !! direct, indirect, special, consequential, incidental or punitive
36     !! damages, however caused and regardless of the theory of liability,
37     !! arising out of the use of or inability to use software, even if the
38     !! University of Notre Dame has been advised of the possibility of
39     !! such damages.
40     !!
41    
42    
43 gezelter 1608 module shapes
44    
45     use force_globals
46     use definitions
47     use atype_module
48     use vector_class
49     use simulation
50     use status
51 gezelter 1633 use lj
52 gezelter 1608 #ifdef IS_MPI
53     use mpiSimulation
54     #endif
55     implicit none
56    
57     PRIVATE
58 chuckv 2355 #define __FORTRAN90
59     #include "UseTheForce/DarkSide/fInteractionMap.h"
60 gezelter 1608 INTEGER, PARAMETER:: CHEBYSHEV_TN = 1
61     INTEGER, PARAMETER:: CHEBYSHEV_UN = 2
62     INTEGER, PARAMETER:: LAGUERRE = 3
63     INTEGER, PARAMETER:: HERMITE = 4
64     INTEGER, PARAMETER:: SH_COS = 0
65     INTEGER, PARAMETER:: SH_SIN = 1
66    
67     logical, save :: haveShapeMap = .false.
68    
69     public :: do_shape_pair
70     public :: newShapeType
71 chrisfen 1647 public :: complete_Shape_FF
72 chuckv 2188 public :: destroyShapeTypes
73 chrisfen 2277 public :: getShapeCut
74 gezelter 1608
75     type, private :: Shape
76     integer :: atid
77     integer :: nContactFuncs
78     integer :: nRangeFuncs
79     integer :: nStrengthFuncs
80     integer :: bigL
81     integer :: bigM
82     integer, pointer, dimension(:) :: ContactFuncLValue => null()
83     integer, pointer, dimension(:) :: ContactFuncMValue => null()
84     integer, pointer, dimension(:) :: ContactFunctionType => null()
85     real(kind=dp), pointer, dimension(:) :: ContactFuncCoefficient => null()
86     integer, pointer, dimension(:) :: RangeFuncLValue => null()
87     integer, pointer, dimension(:) :: RangeFuncMValue => null()
88     integer, pointer, dimension(:) :: RangeFunctionType => null()
89     real(kind=dp), pointer, dimension(:) :: RangeFuncCoefficient => null()
90     integer, pointer, dimension(:) :: StrengthFuncLValue => null()
91     integer, pointer, dimension(:) :: StrengthFuncMValue => null()
92     integer, pointer, dimension(:) :: StrengthFunctionType => null()
93     real(kind=dp), pointer, dimension(:) :: StrengthFuncCoefficient => null()
94     logical :: isLJ
95     real ( kind = dp ) :: epsilon
96     real ( kind = dp ) :: sigma
97     end type Shape
98 gezelter 2204
99 gezelter 1608 type, private :: ShapeList
100     integer :: n_shapes = 0
101     integer :: currentShape = 0
102 chrisfen 2214 type(Shape), pointer :: Shapes(:) => null()
103     integer, pointer :: atidToShape(:) => null()
104 gezelter 1608 end type ShapeList
105 chrisfen 2214
106 gezelter 1608 type(ShapeList), save :: ShapeMap
107 chrisfen 2214
108 gezelter 1608 integer :: lmax
109 chrisfen 2214
110 gezelter 1608 contains
111 chrisfen 2214
112 gezelter 1608 subroutine newShapeType(nContactFuncs, ContactFuncLValue, &
113     ContactFuncMValue, ContactFunctionType, ContactFuncCoefficient, &
114     nRangeFuncs, RangeFuncLValue, RangeFuncMValue, RangeFunctionType, &
115     RangeFuncCoefficient, nStrengthFuncs, StrengthFuncLValue, &
116     StrengthFuncMValue, StrengthFunctionType, StrengthFuncCoefficient, &
117 chrisfen 2211 c_ident, status)
118 chrisfen 2214
119 gezelter 1608 integer :: nContactFuncs
120     integer :: nRangeFuncs
121     integer :: nStrengthFuncs
122     integer :: shape_ident
123     integer :: status
124 chrisfen 2211 integer :: c_ident
125 chrisfen 1689 integer :: myATID
126 gezelter 1608 integer :: bigL
127     integer :: bigM
128     integer :: j, me, nShapeTypes, nLJTypes, ntypes, current, alloc_stat
129     integer, pointer :: MatchList(:) => null()
130    
131     integer, dimension(nContactFuncs) :: ContactFuncLValue
132     integer, dimension(nContactFuncs) :: ContactFuncMValue
133     integer, dimension(nContactFuncs) :: ContactFunctionType
134     real(kind=dp), dimension(nContactFuncs) :: ContactFuncCoefficient
135     integer, dimension(nRangeFuncs) :: RangeFuncLValue
136     integer, dimension(nRangeFuncs) :: RangeFuncMValue
137     integer, dimension(nRangeFuncs) :: RangeFunctionType
138     real(kind=dp), dimension(nRangeFuncs) :: RangeFuncCoefficient
139     integer, dimension(nStrengthFuncs) :: StrengthFuncLValue
140     integer, dimension(nStrengthFuncs) :: StrengthFuncMValue
141     integer, dimension(nStrengthFuncs) :: StrengthFunctionType
142     real(kind=dp), dimension(nStrengthFuncs) :: StrengthFuncCoefficient
143    
144     status = 0
145     ! check to see if this is the first time into this routine...
146     if (.not.associated(ShapeMap%Shapes)) then
147    
148     call getMatchingElementList(atypes, "is_Shape", .true., &
149     nShapeTypes, MatchList)
150 gezelter 2204
151 gezelter 1633 call getMatchingElementList(atypes, "is_LennardJones", .true., &
152 gezelter 1608 nLJTypes, MatchList)
153 gezelter 2204
154 gezelter 1608 ShapeMap%n_shapes = nShapeTypes + nLJTypes
155 gezelter 2204
156 gezelter 1608 allocate(ShapeMap%Shapes(nShapeTypes + nLJTypes))
157 gezelter 2204
158 gezelter 1608 ntypes = getSize(atypes)
159 chrisfen 2214
160 chrisfen 2211 allocate(ShapeMap%atidToShape(ntypes))
161 gezelter 1608 end if
162 gezelter 2204
163 gezelter 1608 ShapeMap%currentShape = ShapeMap%currentShape + 1
164     current = ShapeMap%currentShape
165    
166     call allocateShape(nContactFuncs, nRangeFuncs, nStrengthFuncs, &
167     ShapeMap%Shapes(current), stat=alloc_stat)
168     if (alloc_stat .ne. 0) then
169     status = -1
170     return
171     endif
172    
173 chrisfen 2214 myATID = getFirstMatchingElement(atypes, "c_ident", c_ident)
174    
175 chrisfen 2211 ShapeMap%atidToShape(myATID) = current
176     ShapeMap%Shapes(current)%atid = myATID
177 gezelter 1608 ShapeMap%Shapes(current)%nContactFuncs = nContactFuncs
178     ShapeMap%Shapes(current)%nRangeFuncs = nRangeFuncs
179     ShapeMap%Shapes(current)%nStrengthFuncs = nStrengthFuncs
180     ShapeMap%Shapes(current)%ContactFuncLValue = ContactFuncLValue
181     ShapeMap%Shapes(current)%ContactFuncMValue = ContactFuncMValue
182     ShapeMap%Shapes(current)%ContactFunctionType = ContactFunctionType
183     ShapeMap%Shapes(current)%ContactFuncCoefficient = ContactFuncCoefficient
184     ShapeMap%Shapes(current)%RangeFuncLValue = RangeFuncLValue
185     ShapeMap%Shapes(current)%RangeFuncMValue = RangeFuncMValue
186     ShapeMap%Shapes(current)%RangeFunctionType = RangeFunctionType
187     ShapeMap%Shapes(current)%RangeFuncCoefficient = RangeFuncCoefficient
188     ShapeMap%Shapes(current)%StrengthFuncLValue = StrengthFuncLValue
189     ShapeMap%Shapes(current)%StrengthFuncMValue = StrengthFuncMValue
190     ShapeMap%Shapes(current)%StrengthFunctionType = StrengthFunctionType
191     ShapeMap%Shapes(current)%StrengthFuncCoefficient = StrengthFuncCoefficient
192    
193     bigL = -1
194     bigM = -1
195 gezelter 2204
196 gezelter 1608 do j = 1, ShapeMap%Shapes(current)%nContactFuncs
197     if (ShapeMap%Shapes(current)%ContactFuncLValue(j) .gt. bigL) then
198     bigL = ShapeMap%Shapes(current)%ContactFuncLValue(j)
199     endif
200     if (ShapeMap%Shapes(current)%ContactFuncMValue(j) .gt. bigM) then
201     bigM = ShapeMap%Shapes(current)%ContactFuncMValue(j)
202     endif
203     enddo
204     do j = 1, ShapeMap%Shapes(current)%nRangeFuncs
205     if (ShapeMap%Shapes(current)%RangeFuncLValue(j) .gt. bigL) then
206     bigL = ShapeMap%Shapes(current)%RangeFuncLValue(j)
207     endif
208     if (ShapeMap%Shapes(current)%RangeFuncMValue(j) .gt. bigM) then
209     bigM = ShapeMap%Shapes(current)%RangeFuncMValue(j)
210     endif
211     enddo
212     do j = 1, ShapeMap%Shapes(current)%nStrengthFuncs
213     if (ShapeMap%Shapes(current)%StrengthFuncLValue(j) .gt. bigL) then
214     bigL = ShapeMap%Shapes(current)%StrengthFuncLValue(j)
215     endif
216     if (ShapeMap%Shapes(current)%StrengthFuncMValue(j) .gt. bigM) then
217     bigM = ShapeMap%Shapes(current)%StrengthFuncMValue(j)
218     endif
219     enddo
220    
221     ShapeMap%Shapes(current)%bigL = bigL
222     ShapeMap%Shapes(current)%bigM = bigM
223    
224     end subroutine newShapeType
225    
226     subroutine allocateShape(nContactFuncs, nRangeFuncs, nStrengthFuncs, &
227     myShape, stat)
228    
229     integer, intent(in) :: nContactFuncs, nRangeFuncs, nStrengthFuncs
230     type(Shape), intent(inout) :: myShape
231     integer, intent(out) :: stat
232     integer :: alloc_stat
233 gezelter 2204
234 chrisfen 1689 stat = 0
235 gezelter 1608 if (associated(myShape%contactFuncLValue)) then
236     deallocate(myShape%contactFuncLValue)
237     endif
238     allocate(myShape%contactFuncLValue(nContactFuncs), stat = alloc_stat)
239     if (alloc_stat .ne. 0) then
240     stat = -1
241     return
242     endif
243     if (associated(myShape%contactFuncMValue)) then
244     deallocate(myShape%contactFuncMValue)
245     endif
246     allocate(myShape%contactFuncMValue(nContactFuncs), stat = alloc_stat)
247     if (alloc_stat .ne. 0) then
248     stat = -1
249     return
250     endif
251     if (associated(myShape%contactFunctionType)) then
252     deallocate(myShape%contactFunctionType)
253     endif
254     allocate(myShape%contactFunctionType(nContactFuncs), stat = alloc_stat)
255     if (alloc_stat .ne. 0) then
256     stat = -1
257     return
258     endif
259     if (associated(myShape%contactFuncCoefficient)) then
260     deallocate(myShape%contactFuncCoefficient)
261     endif
262     allocate(myShape%contactFuncCoefficient(nContactFuncs), stat = alloc_stat)
263     if (alloc_stat .ne. 0) then
264     stat = -1
265     return
266     endif
267    
268     if (associated(myShape%rangeFuncLValue)) then
269     deallocate(myShape%rangeFuncLValue)
270     endif
271     allocate(myShape%rangeFuncLValue(nRangeFuncs), stat = alloc_stat)
272     if (alloc_stat .ne. 0) then
273     stat = -1
274     return
275     endif
276     if (associated(myShape%rangeFuncMValue)) then
277     deallocate(myShape%rangeFuncMValue)
278     endif
279     allocate(myShape%rangeFuncMValue(nRangeFuncs), stat = alloc_stat)
280     if (alloc_stat .ne. 0) then
281     stat = -1
282     return
283     endif
284     if (associated(myShape%rangeFunctionType)) then
285     deallocate(myShape%rangeFunctionType)
286     endif
287     allocate(myShape%rangeFunctionType(nRangeFuncs), stat = alloc_stat)
288     if (alloc_stat .ne. 0) then
289     stat = -1
290     return
291     endif
292     if (associated(myShape%rangeFuncCoefficient)) then
293     deallocate(myShape%rangeFuncCoefficient)
294     endif
295     allocate(myShape%rangeFuncCoefficient(nRangeFuncs), stat = alloc_stat)
296     if (alloc_stat .ne. 0) then
297     stat = -1
298     return
299     endif
300 chrisfen 1689
301 gezelter 1608 if (associated(myShape%strengthFuncLValue)) then
302     deallocate(myShape%strengthFuncLValue)
303     endif
304     allocate(myShape%strengthFuncLValue(nStrengthFuncs), stat = alloc_stat)
305     if (alloc_stat .ne. 0) then
306     stat = -1
307     return
308     endif
309     if (associated(myShape%strengthFuncMValue)) then
310     deallocate(myShape%strengthFuncMValue)
311     endif
312     allocate(myShape%strengthFuncMValue(nStrengthFuncs), stat = alloc_stat)
313     if (alloc_stat .ne. 0) then
314     stat = -1
315     return
316     endif
317     if (associated(myShape%strengthFunctionType)) then
318     deallocate(myShape%strengthFunctionType)
319     endif
320     allocate(myShape%strengthFunctionType(nStrengthFuncs), stat = alloc_stat)
321     if (alloc_stat .ne. 0) then
322     stat = -1
323     return
324     endif
325     if (associated(myShape%strengthFuncCoefficient)) then
326     deallocate(myShape%strengthFuncCoefficient)
327     endif
328     allocate(myShape%strengthFuncCoefficient(nStrengthFuncs), stat=alloc_stat)
329     if (alloc_stat .ne. 0) then
330     stat = -1
331     return
332     endif
333    
334 chrisfen 1689 return
335    
336 gezelter 1608 end subroutine allocateShape
337 gezelter 2204
338 chrisfen 1647 subroutine complete_Shape_FF(status)
339 gezelter 1608 integer :: status
340     integer :: i, j, l, m, lm, function_type
341 chrisfen 1647 real(kind=dp) :: thisDP, sigma
342 chrisfen 2211 integer :: alloc_stat, iTheta, iPhi, nSteps, nAtypes, myATID, current
343 gezelter 1608 logical :: thisProperty
344    
345     status = 0
346     if (ShapeMap%currentShape == 0) then
347     call handleError("init_Shape_FF", "No members in ShapeMap")
348     status = -1
349     return
350     end if
351 gezelter 2204
352 gezelter 1608 nAtypes = getSize(atypes)
353    
354     if (nAtypes == 0) then
355     status = -1
356     return
357 chrisfen 2211 end if
358 gezelter 1608
359 chrisfen 1689 ! atypes comes from c side
360 chrisfen 2211 do i = 1, nAtypes
361    
362     myATID = getFirstMatchingElement(atypes, 'c_ident', i)
363     call getElementProperty(atypes, myATID, "is_LennardJones", thisProperty)
364 chrisfen 2214
365 gezelter 1608 if (thisProperty) then
366     ShapeMap%currentShape = ShapeMap%currentShape + 1
367     current = ShapeMap%currentShape
368    
369 chrisfen 2211 ShapeMap%atidToShape(myATID) = current
370     ShapeMap%Shapes(current)%atid = myATID
371 gezelter 1608
372     ShapeMap%Shapes(current)%isLJ = .true.
373    
374 chrisfen 2211 ShapeMap%Shapes(current)%epsilon = getEpsilon(myATID)
375     ShapeMap%Shapes(current)%sigma = getSigma(myATID)
376 gezelter 2204
377 gezelter 1608 endif
378 gezelter 2204
379 gezelter 1608 end do
380    
381     haveShapeMap = .true.
382 gezelter 2204
383 chrisfen 2211 ! do i = 1, ShapeMap%n_shapes
384     ! write(*,*) 'i = ', i, ' isLJ = ', ShapeMap%Shapes(i)%isLJ
385     ! end do
386    
387 chrisfen 1647 end subroutine complete_Shape_FF
388 gezelter 2204
389 chrisfen 2277 function getShapeCut(atomID) result(cutValue)
390     integer, intent(in) :: atomID
391     real(kind=dp) :: cutValue, whoopdedoo
392    
393     !! this is just a placeholder for a cutoff value, hopefully we'll
394     !! develop a method to calculate a sensible value
395     whoopdedoo = 9.0_dp
396    
397     cutValue = whoopdedoo
398    
399     end function getShapeCut
400    
401 gezelter 1608 subroutine do_shape_pair(atom1, atom2, d, rij, r2, sw, vpair, fpair, &
402     pot, A, f, t, do_pot)
403 gezelter 2204
404 chrisfen 1689 INTEGER, PARAMETER:: LMAX = 64
405     INTEGER, PARAMETER:: MMAX = 64
406    
407 gezelter 1608 integer, intent(in) :: atom1, atom2
408     real (kind=dp), intent(inout) :: rij, r2
409     real (kind=dp), dimension(3), intent(in) :: d
410     real (kind=dp), dimension(3), intent(inout) :: fpair
411 chrisfen 1717 real (kind=dp) :: pot, vpair, sw, dswdr
412 gezelter 1608 real (kind=dp), dimension(9,nLocal) :: A
413     real (kind=dp), dimension(3,nLocal) :: f
414     real (kind=dp), dimension(3,nLocal) :: t
415     logical, intent(in) :: do_pot
416    
417     real (kind=dp) :: r3, r5, rt2, rt3, rt5, rt6, rt11, rt12, rt126
418     integer :: atid1, atid2, st1, st2
419     integer :: l, m, lm, id1, id2, localError, function_type
420     real (kind=dp) :: sigma_i, s_i, eps_i, sigma_j, s_j, eps_j
421     real (kind=dp) :: coeff
422 chrisfen 1717 real (kind=dp) :: pot_temp
423 gezelter 1608
424     real (kind=dp) :: dsigmaidx, dsigmaidy, dsigmaidz
425     real (kind=dp) :: dsigmaidux, dsigmaiduy, dsigmaiduz
426     real (kind=dp) :: dsigmajdx, dsigmajdy, dsigmajdz
427     real (kind=dp) :: dsigmajdux, dsigmajduy, dsigmajduz
428    
429     real (kind=dp) :: dsidx, dsidy, dsidz
430     real (kind=dp) :: dsidux, dsiduy, dsiduz
431     real (kind=dp) :: dsjdx, dsjdy, dsjdz
432     real (kind=dp) :: dsjdux, dsjduy, dsjduz
433    
434     real (kind=dp) :: depsidx, depsidy, depsidz
435     real (kind=dp) :: depsidux, depsiduy, depsiduz
436     real (kind=dp) :: depsjdx, depsjdy, depsjdz
437     real (kind=dp) :: depsjdux, depsjduy, depsjduz
438    
439     real (kind=dp) :: xi, yi, zi, xj, yj, zj, xi2, yi2, zi2, xj2, yj2, zj2
440    
441 gezelter 1707 real (kind=dp) :: sti2, stj2
442    
443 gezelter 1608 real (kind=dp) :: proji, proji3, projj, projj3
444     real (kind=dp) :: cti, ctj, cpi, cpj, spi, spj
445     real (kind=dp) :: Phunc, sigma, s, eps, rtdenom, rt
446    
447     real (kind=dp) :: dctidx, dctidy, dctidz
448     real (kind=dp) :: dctidux, dctiduy, dctiduz
449     real (kind=dp) :: dctjdx, dctjdy, dctjdz
450     real (kind=dp) :: dctjdux, dctjduy, dctjduz
451    
452     real (kind=dp) :: dcpidx, dcpidy, dcpidz
453     real (kind=dp) :: dcpidux, dcpiduy, dcpiduz
454     real (kind=dp) :: dcpjdx, dcpjdy, dcpjdz
455     real (kind=dp) :: dcpjdux, dcpjduy, dcpjduz
456    
457     real (kind=dp) :: dspidx, dspidy, dspidz
458     real (kind=dp) :: dspidux, dspiduy, dspiduz
459     real (kind=dp) :: dspjdx, dspjdy, dspjdz
460     real (kind=dp) :: dspjdux, dspjduy, dspjduz
461    
462     real (kind=dp) :: dPhuncdX, dPhuncdY, dPhuncdZ
463     real (kind=dp) :: dPhuncdUx, dPhuncdUy, dPhuncdUz
464    
465     real (kind=dp) :: dsigmadxi, dsigmadyi, dsigmadzi
466     real (kind=dp) :: dsigmaduxi, dsigmaduyi, dsigmaduzi
467     real (kind=dp) :: dsigmadxj, dsigmadyj, dsigmadzj
468     real (kind=dp) :: dsigmaduxj, dsigmaduyj, dsigmaduzj
469    
470     real (kind=dp) :: dsdxi, dsdyi, dsdzi
471     real (kind=dp) :: dsduxi, dsduyi, dsduzi
472     real (kind=dp) :: dsdxj, dsdyj, dsdzj
473     real (kind=dp) :: dsduxj, dsduyj, dsduzj
474 gezelter 2204
475 gezelter 1608 real (kind=dp) :: depsdxi, depsdyi, depsdzi
476     real (kind=dp) :: depsduxi, depsduyi, depsduzi
477     real (kind=dp) :: depsdxj, depsdyj, depsdzj
478     real (kind=dp) :: depsduxj, depsduyj, depsduzj
479    
480     real (kind=dp) :: drtdxi, drtdyi, drtdzi
481     real (kind=dp) :: drtduxi, drtduyi, drtduzi
482     real (kind=dp) :: drtdxj, drtdyj, drtdzj
483     real (kind=dp) :: drtduxj, drtduyj, drtduzj
484    
485     real (kind=dp) :: drdxi, drdyi, drdzi
486     real (kind=dp) :: drduxi, drduyi, drduzi
487     real (kind=dp) :: drdxj, drdyj, drdzj
488     real (kind=dp) :: drduxj, drduyj, drduzj
489    
490     real (kind=dp) :: dvdxi, dvdyi, dvdzi
491     real (kind=dp) :: dvduxi, dvduyi, dvduzi
492     real (kind=dp) :: dvdxj, dvdyj, dvdzj
493     real (kind=dp) :: dvduxj, dvduyj, dvduzj
494    
495     real (kind=dp) :: fxi, fyi, fzi, fxj, fyj, fzj
496     real (kind=dp) :: txi, tyi, tzi, txj, tyj, tzj
497     real (kind=dp) :: fxii, fyii, fzii, fxij, fyij, fzij
498     real (kind=dp) :: fxji, fyji, fzji, fxjj, fyjj, fzjj
499     real (kind=dp) :: fxradial, fyradial, fzradial
500    
501 chrisfen 2214 real (kind=dp) :: xihat, yihat, zihat, xjhat, yjhat, zjhat
502    
503 chrisfen 1698 real (kind=dp) :: plm_i(0:LMAX,0:MMAX), dlm_i(0:LMAX,0:MMAX)
504     real (kind=dp) :: plm_j(0:LMAX,0:MMAX), dlm_j(0:LMAX,0:MMAX)
505     real (kind=dp) :: tm_i(0:MMAX), dtm_i(0:MMAX), um_i(0:MMAX), dum_i(0:MMAX)
506     real (kind=dp) :: tm_j(0:MMAX), dtm_j(0:MMAX), um_j(0:MMAX), dum_j(0:MMAX)
507 chrisfen 1689
508 gezelter 1608 if (.not.haveShapeMap) then
509     call handleError("calc_shape", "NO SHAPEMAP!!!!")
510     return
511     endif
512 gezelter 2204
513 gezelter 1608 !! We assume that the rotation matrices have already been calculated
514     !! and placed in the A array.
515     r3 = r2*rij
516     r5 = r3*r2
517 gezelter 2204
518 gezelter 1608 drdxi = -d(1) / rij
519     drdyi = -d(2) / rij
520     drdzi = -d(3) / rij
521 gezelter 2756 drduxi = 0.0_dp
522     drduyi = 0.0_dp
523     drduzi = 0.0_dp
524 gezelter 1608
525     drdxj = d(1) / rij
526     drdyj = d(2) / rij
527     drdzj = d(3) / rij
528 gezelter 2756 drduxj = 0.0_dp
529     drduyj = 0.0_dp
530     drduzj = 0.0_dp
531 gezelter 2204
532 gezelter 1608 ! find the atom type id (atid) for each atom:
533     #ifdef IS_MPI
534     atid1 = atid_Row(atom1)
535     atid2 = atid_Col(atom2)
536     #else
537     atid1 = atid(atom1)
538     atid2 = atid(atom2)
539     #endif
540    
541     ! use the atid to find the shape type (st) for each atom:
542     st1 = ShapeMap%atidToShape(atid1)
543     st2 = ShapeMap%atidToShape(atid2)
544 chrisfen 2211
545     ! write(*,*) atom1, atom2, atid1, atid2, st1, st2, ShapeMap%Shapes(st1)%isLJ, ShapeMap%Shapes(st2)%isLJ
546 chrisfen 1689
547 gezelter 1608 if (ShapeMap%Shapes(st1)%isLJ) then
548 chrisfen 1689
549 gezelter 1608 sigma_i = ShapeMap%Shapes(st1)%sigma
550     s_i = ShapeMap%Shapes(st1)%sigma
551     eps_i = ShapeMap%Shapes(st1)%epsilon
552 gezelter 2756 dsigmaidx = 0.0_dp
553     dsigmaidy = 0.0_dp
554     dsigmaidz = 0.0_dp
555     dsigmaidux = 0.0_dp
556     dsigmaiduy = 0.0_dp
557     dsigmaiduz = 0.0_dp
558     dsidx = 0.0_dp
559     dsidy = 0.0_dp
560     dsidz = 0.0_dp
561     dsidux = 0.0_dp
562     dsiduy = 0.0_dp
563     dsiduz = 0.0_dp
564     depsidx = 0.0_dp
565     depsidy = 0.0_dp
566     depsidz = 0.0_dp
567     depsidux = 0.0_dp
568     depsiduy = 0.0_dp
569     depsiduz = 0.0_dp
570 gezelter 1608 else
571    
572     #ifdef IS_MPI
573     ! rotate the inter-particle separation into the two different
574     ! body-fixed coordinate systems:
575 gezelter 2204
576 gezelter 1608 xi = A_row(1,atom1)*d(1) + A_row(2,atom1)*d(2) + A_row(3,atom1)*d(3)
577     yi = A_row(4,atom1)*d(1) + A_row(5,atom1)*d(2) + A_row(6,atom1)*d(3)
578     zi = A_row(7,atom1)*d(1) + A_row(8,atom1)*d(2) + A_row(9,atom1)*d(3)
579 gezelter 2204
580 gezelter 1608 #else
581     ! rotate the inter-particle separation into the two different
582     ! body-fixed coordinate systems:
583 gezelter 2204
584 gezelter 1608 xi = a(1,atom1)*d(1) + a(2,atom1)*d(2) + a(3,atom1)*d(3)
585     yi = a(4,atom1)*d(1) + a(5,atom1)*d(2) + a(6,atom1)*d(3)
586     zi = a(7,atom1)*d(1) + a(8,atom1)*d(2) + a(9,atom1)*d(3)
587 gezelter 2204
588 gezelter 1608 #endif
589 chrisfen 2214 xihat = xi / rij
590     yihat = yi / rij
591     zihat = zi / rij
592 gezelter 1608 xi2 = xi*xi
593     yi2 = yi*yi
594 gezelter 1707 zi2 = zi*zi
595 gezelter 1608 cti = zi / rij
596 chrisfen 1689
597 gezelter 1707 if (cti .gt. 1.0_dp) cti = 1.0_dp
598     if (cti .lt. -1.0_dp) cti = -1.0_dp
599    
600 gezelter 1608 dctidx = - zi * xi / r3
601     dctidy = - zi * yi / r3
602 gezelter 2756 dctidz = 1.0_dp / rij - zi2 / r3
603 chrisfen 2214 dctidux = yi / rij ! - (zi * xi2) / r3
604     dctiduy = -xi / rij !- (zi * yi2) / r3
605 gezelter 2756 dctiduz = 0.0_dp !zi / rij - (zi2 * zi) / r3
606 gezelter 1707
607     ! this is an attempt to try to truncate the singularity when
608     ! sin(theta) is near 0.0:
609    
610     sti2 = 1.0_dp - cti*cti
611 gezelter 2756 if (abs(sti2) .lt. 1.0e-12_dp) then
612     proji = sqrt(rij * 1.0e-12_dp)
613     dcpidx = 1.0_dp / proji
614     dcpidy = 0.0_dp
615 chrisfen 1717 dcpidux = xi / proji
616 gezelter 2756 dcpiduy = 0.0_dp
617     dspidx = 0.0_dp
618     dspidy = 1.0_dp / proji
619     dspidux = 0.0_dp
620 chrisfen 1717 dspiduy = yi / proji
621 gezelter 1707 else
622     proji = sqrt(xi2 + yi2)
623     proji3 = proji*proji*proji
624 gezelter 2756 dcpidx = 1.0_dp / proji - xi2 / proji3
625 gezelter 1707 dcpidy = - xi * yi / proji3
626 chrisfen 1717 dcpidux = xi / proji - (xi2 * xi) / proji3
627     dcpiduy = - (xi * yi2) / proji3
628 gezelter 1707 dspidx = - xi * yi / proji3
629 gezelter 2756 dspidy = 1.0_dp / proji - yi2 / proji3
630 chrisfen 1717 dspidux = - (yi * xi2) / proji3
631     dspiduy = yi / proji - (yi2 * yi) / proji3
632 gezelter 1707 endif
633 gezelter 2204
634 gezelter 1608 cpi = xi / proji
635 gezelter 2756 dcpidz = 0.0_dp
636     dcpiduz = 0.0_dp
637 gezelter 2204
638 gezelter 1608 spi = yi / proji
639 gezelter 2756 dspidz = 0.0_dp
640     dspiduz = 0.0_dp
641 gezelter 1608
642 chrisfen 1698 call Associated_Legendre(cti, ShapeMap%Shapes(st1)%bigM, &
643     ShapeMap%Shapes(st1)%bigL, LMAX, &
644 chrisfen 1689 plm_i, dlm_i)
645 gezelter 1608
646 chrisfen 1689 call Orthogonal_Polynomial(cpi, ShapeMap%Shapes(st1)%bigM, MMAX, &
647 gezelter 1608 CHEBYSHEV_TN, tm_i, dtm_i)
648 chrisfen 1689 call Orthogonal_Polynomial(cpi, ShapeMap%Shapes(st1)%bigM, MMAX, &
649 gezelter 1608 CHEBYSHEV_UN, um_i, dum_i)
650 gezelter 2204
651 gezelter 2756 sigma_i = 0.0_dp
652     s_i = 0.0_dp
653     eps_i = 0.0_dp
654     dsigmaidx = 0.0_dp
655     dsigmaidy = 0.0_dp
656     dsigmaidz = 0.0_dp
657     dsigmaidux = 0.0_dp
658     dsigmaiduy = 0.0_dp
659     dsigmaiduz = 0.0_dp
660     dsidx = 0.0_dp
661     dsidy = 0.0_dp
662     dsidz = 0.0_dp
663     dsidux = 0.0_dp
664     dsiduy = 0.0_dp
665     dsiduz = 0.0_dp
666     depsidx = 0.0_dp
667     depsidy = 0.0_dp
668     depsidz = 0.0_dp
669     depsidux = 0.0_dp
670     depsiduy = 0.0_dp
671     depsiduz = 0.0_dp
672 gezelter 1608
673     do lm = 1, ShapeMap%Shapes(st1)%nContactFuncs
674     l = ShapeMap%Shapes(st1)%ContactFuncLValue(lm)
675     m = ShapeMap%Shapes(st1)%ContactFuncMValue(lm)
676     coeff = ShapeMap%Shapes(st1)%ContactFuncCoefficient(lm)
677     function_type = ShapeMap%Shapes(st1)%ContactFunctionType(lm)
678    
679     if ((function_type .eq. SH_COS).or.(m.eq.0)) then
680     Phunc = coeff * tm_i(m)
681     dPhuncdX = coeff * dtm_i(m) * dcpidx
682     dPhuncdY = coeff * dtm_i(m) * dcpidy
683     dPhuncdZ = coeff * dtm_i(m) * dcpidz
684 chrisfen 2214 dPhuncdUx = coeff * dtm_i(m) * dcpidux
685 gezelter 1608 dPhuncdUy = coeff * dtm_i(m) * dcpiduy
686     dPhuncdUz = coeff * dtm_i(m) * dcpiduz
687     else
688     Phunc = coeff * spi * um_i(m-1)
689     dPhuncdX = coeff * (spi * dum_i(m-1) * dcpidx + dspidx *um_i(m-1))
690     dPhuncdY = coeff * (spi * dum_i(m-1) * dcpidy + dspidy *um_i(m-1))
691     dPhuncdZ = coeff * (spi * dum_i(m-1) * dcpidz + dspidz *um_i(m-1))
692     dPhuncdUx = coeff*(spi * dum_i(m-1)*dcpidux + dspidux *um_i(m-1))
693     dPhuncdUy = coeff*(spi * dum_i(m-1)*dcpiduy + dspiduy *um_i(m-1))
694     dPhuncdUz = coeff*(spi * dum_i(m-1)*dcpiduz + dspiduz *um_i(m-1))
695     endif
696    
697 chrisfen 1698 sigma_i = sigma_i + plm_i(m,l)*Phunc
698 chrisfen 2214 !!$ write(*,*) 'dsigmaidux = ', dsigmaidux
699     !!$ write(*,*) 'Phunc = ', Phunc
700 chrisfen 1698 dsigmaidx = dsigmaidx + plm_i(m,l)*dPhuncdX + &
701     Phunc * dlm_i(m,l) * dctidx
702     dsigmaidy = dsigmaidy + plm_i(m,l)*dPhuncdY + &
703     Phunc * dlm_i(m,l) * dctidy
704     dsigmaidz = dsigmaidz + plm_i(m,l)*dPhuncdZ + &
705     Phunc * dlm_i(m,l) * dctidz
706     dsigmaidux = dsigmaidux + plm_i(m,l)* dPhuncdUx + &
707     Phunc * dlm_i(m,l) * dctidux
708     dsigmaiduy = dsigmaiduy + plm_i(m,l)* dPhuncdUy + &
709     Phunc * dlm_i(m,l) * dctiduy
710     dsigmaiduz = dsigmaiduz + plm_i(m,l)* dPhuncdUz + &
711     Phunc * dlm_i(m,l) * dctiduz
712 chrisfen 2214 !!$ write(*,*) 'dsigmaidux = ', dsigmaidux, '; dPhuncdUx = ', dPhuncdUx, &
713     !!$ '; dctidux = ', dctidux, '; plm_i(m,l) = ', plm_i(m,l), &
714     !!$ '; dlm_i(m,l) = ', dlm_i(m,l), '; m = ', m, '; l = ', l
715 gezelter 1608 end do
716    
717     do lm = 1, ShapeMap%Shapes(st1)%nRangeFuncs
718     l = ShapeMap%Shapes(st1)%RangeFuncLValue(lm)
719     m = ShapeMap%Shapes(st1)%RangeFuncMValue(lm)
720     coeff = ShapeMap%Shapes(st1)%RangeFuncCoefficient(lm)
721     function_type = ShapeMap%Shapes(st1)%RangeFunctionType(lm)
722 gezelter 2204
723 gezelter 1608 if ((function_type .eq. SH_COS).or.(m.eq.0)) then
724     Phunc = coeff * tm_i(m)
725     dPhuncdX = coeff * dtm_i(m) * dcpidx
726     dPhuncdY = coeff * dtm_i(m) * dcpidy
727     dPhuncdZ = coeff * dtm_i(m) * dcpidz
728 chrisfen 2214 dPhuncdUx = coeff * dtm_i(m) * dcpidux
729 gezelter 1608 dPhuncdUy = coeff * dtm_i(m) * dcpiduy
730     dPhuncdUz = coeff * dtm_i(m) * dcpiduz
731     else
732     Phunc = coeff * spi * um_i(m-1)
733     dPhuncdX = coeff * (spi * dum_i(m-1) * dcpidx + dspidx *um_i(m-1))
734     dPhuncdY = coeff * (spi * dum_i(m-1) * dcpidy + dspidy *um_i(m-1))
735     dPhuncdZ = coeff * (spi * dum_i(m-1) * dcpidz + dspidz *um_i(m-1))
736     dPhuncdUx = coeff*(spi * dum_i(m-1)*dcpidux + dspidux *um_i(m-1))
737     dPhuncdUy = coeff*(spi * dum_i(m-1)*dcpiduy + dspiduy *um_i(m-1))
738     dPhuncdUz = coeff*(spi * dum_i(m-1)*dcpiduz + dspiduz *um_i(m-1))
739     endif
740    
741 chrisfen 1698 s_i = s_i + plm_i(m,l)*Phunc
742 gezelter 2204
743 chrisfen 1698 dsidx = dsidx + plm_i(m,l)*dPhuncdX + &
744     Phunc * dlm_i(m,l) * dctidx
745     dsidy = dsidy + plm_i(m,l)*dPhuncdY + &
746     Phunc * dlm_i(m,l) * dctidy
747     dsidz = dsidz + plm_i(m,l)*dPhuncdZ + &
748     Phunc * dlm_i(m,l) * dctidz
749 gezelter 2204
750 chrisfen 1698 dsidux = dsidux + plm_i(m,l)* dPhuncdUx + &
751     Phunc * dlm_i(m,l) * dctidux
752     dsiduy = dsiduy + plm_i(m,l)* dPhuncdUy + &
753     Phunc * dlm_i(m,l) * dctiduy
754     dsiduz = dsiduz + plm_i(m,l)* dPhuncdUz + &
755     Phunc * dlm_i(m,l) * dctiduz
756 gezelter 1608
757     end do
758 gezelter 2204
759 gezelter 1608 do lm = 1, ShapeMap%Shapes(st1)%nStrengthFuncs
760     l = ShapeMap%Shapes(st1)%StrengthFuncLValue(lm)
761     m = ShapeMap%Shapes(st1)%StrengthFuncMValue(lm)
762     coeff = ShapeMap%Shapes(st1)%StrengthFuncCoefficient(lm)
763     function_type = ShapeMap%Shapes(st1)%StrengthFunctionType(lm)
764 gezelter 2204
765 gezelter 1608 if ((function_type .eq. SH_COS).or.(m.eq.0)) then
766     Phunc = coeff * tm_i(m)
767     dPhuncdX = coeff * dtm_i(m) * dcpidx
768     dPhuncdY = coeff * dtm_i(m) * dcpidy
769     dPhuncdZ = coeff * dtm_i(m) * dcpidz
770 chrisfen 2214 dPhuncdUx = coeff * dtm_i(m) * dcpidux
771 gezelter 1608 dPhuncdUy = coeff * dtm_i(m) * dcpiduy
772     dPhuncdUz = coeff * dtm_i(m) * dcpiduz
773     else
774     Phunc = coeff * spi * um_i(m-1)
775     dPhuncdX = coeff * (spi * dum_i(m-1) * dcpidx + dspidx *um_i(m-1))
776     dPhuncdY = coeff * (spi * dum_i(m-1) * dcpidy + dspidy *um_i(m-1))
777     dPhuncdZ = coeff * (spi * dum_i(m-1) * dcpidz + dspidz *um_i(m-1))
778     dPhuncdUx = coeff*(spi * dum_i(m-1)*dcpidux + dspidux *um_i(m-1))
779     dPhuncdUy = coeff*(spi * dum_i(m-1)*dcpiduy + dspiduy *um_i(m-1))
780     dPhuncdUz = coeff*(spi * dum_i(m-1)*dcpiduz + dspiduz *um_i(m-1))
781     endif
782 chrisfen 1698
783     eps_i = eps_i + plm_i(m,l)*Phunc
784 gezelter 2204
785 chrisfen 1698 depsidx = depsidx + plm_i(m,l)*dPhuncdX + &
786     Phunc * dlm_i(m,l) * dctidx
787     depsidy = depsidy + plm_i(m,l)*dPhuncdY + &
788     Phunc * dlm_i(m,l) * dctidy
789     depsidz = depsidz + plm_i(m,l)*dPhuncdZ + &
790     Phunc * dlm_i(m,l) * dctidz
791 gezelter 2204
792 chrisfen 1698 depsidux = depsidux + plm_i(m,l)* dPhuncdUx + &
793     Phunc * dlm_i(m,l) * dctidux
794     depsiduy = depsiduy + plm_i(m,l)* dPhuncdUy + &
795     Phunc * dlm_i(m,l) * dctiduy
796     depsiduz = depsiduz + plm_i(m,l)* dPhuncdUz + &
797     Phunc * dlm_i(m,l) * dctiduz
798 gezelter 1608
799     end do
800    
801     endif
802    
803 gezelter 2204 ! now do j:
804    
805 gezelter 1608 if (ShapeMap%Shapes(st2)%isLJ) then
806     sigma_j = ShapeMap%Shapes(st2)%sigma
807     s_j = ShapeMap%Shapes(st2)%sigma
808     eps_j = ShapeMap%Shapes(st2)%epsilon
809 gezelter 2756 dsigmajdx = 0.0_dp
810     dsigmajdy = 0.0_dp
811     dsigmajdz = 0.0_dp
812     dsigmajdux = 0.0_dp
813     dsigmajduy = 0.0_dp
814     dsigmajduz = 0.0_dp
815     dsjdx = 0.0_dp
816     dsjdy = 0.0_dp
817     dsjdz = 0.0_dp
818     dsjdux = 0.0_dp
819     dsjduy = 0.0_dp
820     dsjduz = 0.0_dp
821     depsjdx = 0.0_dp
822     depsjdy = 0.0_dp
823     depsjdz = 0.0_dp
824     depsjdux = 0.0_dp
825     depsjduy = 0.0_dp
826     depsjduz = 0.0_dp
827 gezelter 1608 else
828 gezelter 2204
829 gezelter 1608 #ifdef IS_MPI
830     ! rotate the inter-particle separation into the two different
831     ! body-fixed coordinate systems:
832     ! negative sign because this is the vector from j to i:
833 gezelter 2204
834 gezelter 1608 xj = -(A_Col(1,atom2)*d(1) + A_Col(2,atom2)*d(2) + A_Col(3,atom2)*d(3))
835     yj = -(A_Col(4,atom2)*d(1) + A_Col(5,atom2)*d(2) + A_Col(6,atom2)*d(3))
836     zj = -(A_Col(7,atom2)*d(1) + A_Col(8,atom2)*d(2) + A_Col(9,atom2)*d(3))
837     #else
838     ! rotate the inter-particle separation into the two different
839     ! body-fixed coordinate systems:
840     ! negative sign because this is the vector from j to i:
841 gezelter 2204
842 gezelter 1608 xj = -(a(1,atom2)*d(1) + a(2,atom2)*d(2) + a(3,atom2)*d(3))
843     yj = -(a(4,atom2)*d(1) + a(5,atom2)*d(2) + a(6,atom2)*d(3))
844     zj = -(a(7,atom2)*d(1) + a(8,atom2)*d(2) + a(9,atom2)*d(3))
845     #endif
846 gezelter 2204
847 chrisfen 2214 xjhat = xj / rij
848     yjhat = yj / rij
849     zjhat = zj / rij
850 gezelter 1608 xj2 = xj*xj
851     yj2 = yj*yj
852     zj2 = zj*zj
853 gezelter 1707 ctj = zj / rij
854 gezelter 2204
855 gezelter 1707 if (ctj .gt. 1.0_dp) ctj = 1.0_dp
856     if (ctj .lt. -1.0_dp) ctj = -1.0_dp
857    
858 gezelter 1608 dctjdx = - zj * xj / r3
859     dctjdy = - zj * yj / r3
860 gezelter 2756 dctjdz = 1.0_dp / rij - zj2 / r3
861 chrisfen 2214 dctjdux = yj / rij !- (zi * xj2) / r3
862     dctjduy = -xj / rij !- (zj * yj2) / r3
863 gezelter 2756 dctjduz = 0.0_dp !zj / rij - (zj2 * zj) / r3
864 gezelter 2204
865 gezelter 1707 ! this is an attempt to try to truncate the singularity when
866     ! sin(theta) is near 0.0:
867    
868     stj2 = 1.0_dp - ctj*ctj
869 gezelter 2756 if (abs(stj2) .lt. 1.0e-12_dp) then
870     projj = sqrt(rij * 1.0e-12_dp)
871     dcpjdx = 1.0_dp / projj
872     dcpjdy = 0.0_dp
873 chrisfen 1717 dcpjdux = xj / projj
874 gezelter 2756 dcpjduy = 0.0_dp
875     dspjdx = 0.0_dp
876     dspjdy = 1.0_dp / projj
877     dspjdux = 0.0_dp
878 chrisfen 1717 dspjduy = yj / projj
879 gezelter 1707 else
880     projj = sqrt(xj2 + yj2)
881     projj3 = projj*projj*projj
882 gezelter 2756 dcpjdx = 1.0_dp / projj - xj2 / projj3
883 gezelter 1707 dcpjdy = - xj * yj / projj3
884 chrisfen 1717 dcpjdux = xj / projj - (xj2 * xj) / projj3
885     dcpjduy = - (xj * yj2) / projj3
886 gezelter 1707 dspjdx = - xj * yj / projj3
887 gezelter 2756 dspjdy = 1.0_dp / projj - yj2 / projj3
888 chrisfen 1717 dspjdux = - (yj * xj2) / projj3
889     dspjduy = yj / projj - (yj2 * yj) / projj3
890 gezelter 1707 endif
891    
892 gezelter 1608 cpj = xj / projj
893 gezelter 2756 dcpjdz = 0.0_dp
894     dcpjduz = 0.0_dp
895 gezelter 2204
896 gezelter 1608 spj = yj / projj
897 gezelter 2756 dspjdz = 0.0_dp
898     dspjduz = 0.0_dp
899 gezelter 1707
900 chrisfen 1717
901 chrisfen 2211 ! write(*,*) 'dcpdu = ' ,dcpidux, dcpiduy, dcpiduz
902     ! write(*,*) 'dcpdu = ' ,dcpjdux, dcpjduy, dcpjduz
903 chrisfen 1698 call Associated_Legendre(ctj, ShapeMap%Shapes(st2)%bigM, &
904     ShapeMap%Shapes(st2)%bigL, LMAX, &
905 chrisfen 1689 plm_j, dlm_j)
906 gezelter 2204
907 chrisfen 1689 call Orthogonal_Polynomial(cpj, ShapeMap%Shapes(st2)%bigM, MMAX, &
908 gezelter 1608 CHEBYSHEV_TN, tm_j, dtm_j)
909 chrisfen 1689 call Orthogonal_Polynomial(cpj, ShapeMap%Shapes(st2)%bigM, MMAX, &
910 gezelter 1608 CHEBYSHEV_UN, um_j, dum_j)
911 gezelter 2204
912 gezelter 2756 sigma_j = 0.0_dp
913     s_j = 0.0_dp
914     eps_j = 0.0_dp
915     dsigmajdx = 0.0_dp
916     dsigmajdy = 0.0_dp
917     dsigmajdz = 0.0_dp
918     dsigmajdux = 0.0_dp
919     dsigmajduy = 0.0_dp
920     dsigmajduz = 0.0_dp
921     dsjdx = 0.0_dp
922     dsjdy = 0.0_dp
923     dsjdz = 0.0_dp
924     dsjdux = 0.0_dp
925     dsjduy = 0.0_dp
926     dsjduz = 0.0_dp
927     depsjdx = 0.0_dp
928     depsjdy = 0.0_dp
929     depsjdz = 0.0_dp
930     depsjdux = 0.0_dp
931     depsjduy = 0.0_dp
932     depsjduz = 0.0_dp
933 gezelter 1608
934     do lm = 1, ShapeMap%Shapes(st2)%nContactFuncs
935     l = ShapeMap%Shapes(st2)%ContactFuncLValue(lm)
936     m = ShapeMap%Shapes(st2)%ContactFuncMValue(lm)
937     coeff = ShapeMap%Shapes(st2)%ContactFuncCoefficient(lm)
938     function_type = ShapeMap%Shapes(st2)%ContactFunctionType(lm)
939    
940     if ((function_type .eq. SH_COS).or.(m.eq.0)) then
941     Phunc = coeff * tm_j(m)
942     dPhuncdX = coeff * dtm_j(m) * dcpjdx
943     dPhuncdY = coeff * dtm_j(m) * dcpjdy
944     dPhuncdZ = coeff * dtm_j(m) * dcpjdz
945 chrisfen 2214 dPhuncdUx = coeff * dtm_j(m) * dcpjdux
946 gezelter 1608 dPhuncdUy = coeff * dtm_j(m) * dcpjduy
947     dPhuncdUz = coeff * dtm_j(m) * dcpjduz
948     else
949     Phunc = coeff * spj * um_j(m-1)
950     dPhuncdX = coeff * (spj * dum_j(m-1) * dcpjdx + dspjdx *um_j(m-1))
951     dPhuncdY = coeff * (spj * dum_j(m-1) * dcpjdy + dspjdy *um_j(m-1))
952     dPhuncdZ = coeff * (spj * dum_j(m-1) * dcpjdz + dspjdz *um_j(m-1))
953     dPhuncdUx = coeff*(spj * dum_j(m-1)*dcpjdux + dspjdux *um_j(m-1))
954     dPhuncdUy = coeff*(spj * dum_j(m-1)*dcpjduy + dspjduy *um_j(m-1))
955     dPhuncdUz = coeff*(spj * dum_j(m-1)*dcpjduz + dspjduz *um_j(m-1))
956     endif
957 gezelter 2204
958 chrisfen 1698 sigma_j = sigma_j + plm_j(m,l)*Phunc
959 gezelter 2204
960 chrisfen 1698 dsigmajdx = dsigmajdx + plm_j(m,l)*dPhuncdX + &
961     Phunc * dlm_j(m,l) * dctjdx
962     dsigmajdy = dsigmajdy + plm_j(m,l)*dPhuncdY + &
963     Phunc * dlm_j(m,l) * dctjdy
964     dsigmajdz = dsigmajdz + plm_j(m,l)*dPhuncdZ + &
965     Phunc * dlm_j(m,l) * dctjdz
966 gezelter 2204
967 chrisfen 1698 dsigmajdux = dsigmajdux + plm_j(m,l)* dPhuncdUx + &
968     Phunc * dlm_j(m,l) * dctjdux
969     dsigmajduy = dsigmajduy + plm_j(m,l)* dPhuncdUy + &
970     Phunc * dlm_j(m,l) * dctjduy
971     dsigmajduz = dsigmajduz + plm_j(m,l)* dPhuncdUz + &
972     Phunc * dlm_j(m,l) * dctjduz
973 gezelter 1608
974     end do
975    
976     do lm = 1, ShapeMap%Shapes(st2)%nRangeFuncs
977     l = ShapeMap%Shapes(st2)%RangeFuncLValue(lm)
978     m = ShapeMap%Shapes(st2)%RangeFuncMValue(lm)
979     coeff = ShapeMap%Shapes(st2)%RangeFuncCoefficient(lm)
980     function_type = ShapeMap%Shapes(st2)%RangeFunctionType(lm)
981    
982     if ((function_type .eq. SH_COS).or.(m.eq.0)) then
983     Phunc = coeff * tm_j(m)
984     dPhuncdX = coeff * dtm_j(m) * dcpjdx
985     dPhuncdY = coeff * dtm_j(m) * dcpjdy
986     dPhuncdZ = coeff * dtm_j(m) * dcpjdz
987 chrisfen 2214 dPhuncdUx = coeff * dtm_j(m) * dcpjdux
988 gezelter 1608 dPhuncdUy = coeff * dtm_j(m) * dcpjduy
989     dPhuncdUz = coeff * dtm_j(m) * dcpjduz
990     else
991     Phunc = coeff * spj * um_j(m-1)
992     dPhuncdX = coeff * (spj * dum_j(m-1) * dcpjdx + dspjdx *um_j(m-1))
993     dPhuncdY = coeff * (spj * dum_j(m-1) * dcpjdy + dspjdy *um_j(m-1))
994     dPhuncdZ = coeff * (spj * dum_j(m-1) * dcpjdz + dspjdz *um_j(m-1))
995     dPhuncdUx = coeff*(spj * dum_j(m-1)*dcpjdux + dspjdux *um_j(m-1))
996     dPhuncdUy = coeff*(spj * dum_j(m-1)*dcpjduy + dspjduy *um_j(m-1))
997     dPhuncdUz = coeff*(spj * dum_j(m-1)*dcpjduz + dspjduz *um_j(m-1))
998     endif
999    
1000 chrisfen 1698 s_j = s_j + plm_j(m,l)*Phunc
1001 gezelter 2204
1002 chrisfen 1698 dsjdx = dsjdx + plm_j(m,l)*dPhuncdX + &
1003     Phunc * dlm_j(m,l) * dctjdx
1004     dsjdy = dsjdy + plm_j(m,l)*dPhuncdY + &
1005     Phunc * dlm_j(m,l) * dctjdy
1006     dsjdz = dsjdz + plm_j(m,l)*dPhuncdZ + &
1007     Phunc * dlm_j(m,l) * dctjdz
1008 gezelter 2204
1009 chrisfen 1698 dsjdux = dsjdux + plm_j(m,l)* dPhuncdUx + &
1010     Phunc * dlm_j(m,l) * dctjdux
1011     dsjduy = dsjduy + plm_j(m,l)* dPhuncdUy + &
1012     Phunc * dlm_j(m,l) * dctjduy
1013     dsjduz = dsjduz + plm_j(m,l)* dPhuncdUz + &
1014     Phunc * dlm_j(m,l) * dctjduz
1015 gezelter 1608
1016     end do
1017    
1018     do lm = 1, ShapeMap%Shapes(st2)%nStrengthFuncs
1019     l = ShapeMap%Shapes(st2)%StrengthFuncLValue(lm)
1020     m = ShapeMap%Shapes(st2)%StrengthFuncMValue(lm)
1021     coeff = ShapeMap%Shapes(st2)%StrengthFuncCoefficient(lm)
1022     function_type = ShapeMap%Shapes(st2)%StrengthFunctionType(lm)
1023    
1024     if ((function_type .eq. SH_COS).or.(m.eq.0)) then
1025     Phunc = coeff * tm_j(m)
1026     dPhuncdX = coeff * dtm_j(m) * dcpjdx
1027     dPhuncdY = coeff * dtm_j(m) * dcpjdy
1028     dPhuncdZ = coeff * dtm_j(m) * dcpjdz
1029     dPhuncdUz = coeff * dtm_j(m) * dcpjdux
1030     dPhuncdUy = coeff * dtm_j(m) * dcpjduy
1031     dPhuncdUz = coeff * dtm_j(m) * dcpjduz
1032     else
1033     Phunc = coeff * spj * um_j(m-1)
1034     dPhuncdX = coeff * (spj * dum_j(m-1) * dcpjdx + dspjdx *um_j(m-1))
1035     dPhuncdY = coeff * (spj * dum_j(m-1) * dcpjdy + dspjdy *um_j(m-1))
1036     dPhuncdZ = coeff * (spj * dum_j(m-1) * dcpjdz + dspjdz *um_j(m-1))
1037     dPhuncdUx = coeff*(spj * dum_j(m-1)*dcpjdux + dspjdux *um_j(m-1))
1038     dPhuncdUy = coeff*(spj * dum_j(m-1)*dcpjduy + dspjduy *um_j(m-1))
1039     dPhuncdUz = coeff*(spj * dum_j(m-1)*dcpjduz + dspjduz *um_j(m-1))
1040     endif
1041    
1042 chrisfen 2211 ! write(*,*) 'l,m = ', l, m, coeff, dPhuncdUx, dPhuncdUy, dPhuncdUz
1043 chrisfen 1717
1044 chrisfen 1698 eps_j = eps_j + plm_j(m,l)*Phunc
1045 gezelter 2204
1046 chrisfen 1698 depsjdx = depsjdx + plm_j(m,l)*dPhuncdX + &
1047     Phunc * dlm_j(m,l) * dctjdx
1048     depsjdy = depsjdy + plm_j(m,l)*dPhuncdY + &
1049     Phunc * dlm_j(m,l) * dctjdy
1050     depsjdz = depsjdz + plm_j(m,l)*dPhuncdZ + &
1051     Phunc * dlm_j(m,l) * dctjdz
1052 gezelter 2204
1053 chrisfen 1698 depsjdux = depsjdux + plm_j(m,l)* dPhuncdUx + &
1054     Phunc * dlm_j(m,l) * dctjdux
1055     depsjduy = depsjduy + plm_j(m,l)* dPhuncdUy + &
1056     Phunc * dlm_j(m,l) * dctjduy
1057     depsjduz = depsjduz + plm_j(m,l)* dPhuncdUz + &
1058     Phunc * dlm_j(m,l) * dctjduz
1059 gezelter 1608
1060     end do
1061    
1062     endif
1063    
1064     ! phew, now let's assemble the potential energy:
1065    
1066     sigma = 0.5*(sigma_i + sigma_j)
1067 chrisfen 2211 ! write(*,*) sigma_i, ' = sigma_i; ', sigma_j, ' = sigma_j'
1068 gezelter 1608 dsigmadxi = 0.5*dsigmaidx
1069     dsigmadyi = 0.5*dsigmaidy
1070     dsigmadzi = 0.5*dsigmaidz
1071     dsigmaduxi = 0.5*dsigmaidux
1072     dsigmaduyi = 0.5*dsigmaiduy
1073     dsigmaduzi = 0.5*dsigmaiduz
1074    
1075     dsigmadxj = 0.5*dsigmajdx
1076     dsigmadyj = 0.5*dsigmajdy
1077     dsigmadzj = 0.5*dsigmajdz
1078     dsigmaduxj = 0.5*dsigmajdux
1079     dsigmaduyj = 0.5*dsigmajduy
1080     dsigmaduzj = 0.5*dsigmajduz
1081    
1082     s = 0.5*(s_i + s_j)
1083    
1084     dsdxi = 0.5*dsidx
1085     dsdyi = 0.5*dsidy
1086     dsdzi = 0.5*dsidz
1087     dsduxi = 0.5*dsidux
1088     dsduyi = 0.5*dsiduy
1089     dsduzi = 0.5*dsiduz
1090    
1091     dsdxj = 0.5*dsjdx
1092     dsdyj = 0.5*dsjdy
1093     dsdzj = 0.5*dsjdz
1094     dsduxj = 0.5*dsjdux
1095     dsduyj = 0.5*dsjduy
1096     dsduzj = 0.5*dsjduz
1097 chrisfen 1698
1098 gezelter 1608 eps = sqrt(eps_i * eps_j)
1099 chrisfen 2214 !!$ write(*,*) 'dsidu = ', dsidux, dsiduy, dsiduz
1100     !!$ write(*,*) 'dsigidu = ', dsigmaidux, dsigmaiduy, dsigmaiduz
1101     !!$ write(*,*) sigma_j, ' is sigma j; ', s_j, ' is s j; ', eps_j, ' is eps j'
1102 gezelter 2756 depsdxi = eps_j * depsidx / (2.0_dp * eps)
1103     depsdyi = eps_j * depsidy / (2.0_dp * eps)
1104     depsdzi = eps_j * depsidz / (2.0_dp * eps)
1105     depsduxi = eps_j * depsidux / (2.0_dp * eps)
1106     depsduyi = eps_j * depsiduy / (2.0_dp * eps)
1107     depsduzi = eps_j * depsiduz / (2.0_dp * eps)
1108 gezelter 1608
1109 gezelter 2756 depsdxj = eps_i * depsjdx / (2.0_dp * eps)
1110     depsdyj = eps_i * depsjdy / (2.0_dp * eps)
1111     depsdzj = eps_i * depsjdz / (2.0_dp * eps)
1112     depsduxj = eps_i * depsjdux / (2.0_dp * eps)
1113     depsduyj = eps_i * depsjduy / (2.0_dp * eps)
1114     depsduzj = eps_i * depsjduz / (2.0_dp * eps)
1115 gezelter 2204
1116 chrisfen 2214 !!$ write(*,*) 'depsidu = ', depsidux, depsiduy, depsiduz
1117 chrisfen 2211
1118 chrisfen 2214 !!$ write(*,*) 'depsjdu = ', depsjdux, depsjduy, depsjduz
1119     !!$ write(*,*) 'depsduj = ', depsduxj, depsduyj, depsduzj
1120 chrisfen 1717 !!$
1121     !!$ write(*,*) 's, sig, eps = ', s, sigma, eps
1122    
1123 gezelter 1608 rtdenom = rij-sigma+s
1124     rt = s / rtdenom
1125    
1126 chrisfen 2214 drtdxi = (dsdxi - rt * (drdxi - dsigmadxi + dsdxi)) / rtdenom
1127     drtdyi = (dsdyi - rt * (drdyi - dsigmadyi + dsdyi)) / rtdenom
1128     drtdzi = (dsdzi - rt * (drdzi - dsigmadzi + dsdzi)) / rtdenom
1129     drtduxi = (dsduxi - rt * (drduxi - dsigmaduxi + dsduxi)) / rtdenom
1130     drtduyi = (dsduyi - rt * (drduyi - dsigmaduyi + dsduyi)) / rtdenom
1131     drtduzi = (dsduzi - rt * (drduzi - dsigmaduzi + dsduzi)) / rtdenom
1132     drtdxj = (dsdxj - rt * (drdxj - dsigmadxj + dsdxj)) / rtdenom
1133     drtdyj = (dsdyj - rt * (drdyj - dsigmadyj + dsdyj)) / rtdenom
1134     drtdzj = (dsdzj - rt * (drdzj - dsigmadzj + dsdzj)) / rtdenom
1135     drtduxj = (dsduxj - rt * (drduxj - dsigmaduxj + dsduxj)) / rtdenom
1136     drtduyj = (dsduyj - rt * (drduyj - dsigmaduyj + dsduyj)) / rtdenom
1137     drtduzj = (dsduzj - rt * (drduzj - dsigmaduzj + dsduzj)) / rtdenom
1138 gezelter 2204
1139 chrisfen 2214 !!$ write(*,*) 'drtd_i = ', drtdxi, drtdyi, drtdzi
1140     !!$ write(*,*) 'drtdu_j = ', drtduxj, drtduyj, drtduzj
1141 chrisfen 2211
1142 gezelter 1608 rt2 = rt*rt
1143     rt3 = rt2*rt
1144     rt5 = rt2*rt3
1145     rt6 = rt3*rt3
1146     rt11 = rt5*rt6
1147     rt12 = rt6*rt6
1148     rt126 = rt12 - rt6
1149    
1150 gezelter 2756 pot_temp = 4.0_dp * eps * rt126
1151 chrisfen 1717
1152     vpair = vpair + pot_temp
1153 gezelter 1608 if (do_pot) then
1154     #ifdef IS_MPI
1155 gezelter 2756 pot_row(VDW_POT,atom1) = pot_row(VDW_POT,atom1) + 0.5_dp*pot_temp*sw
1156     pot_col(VDW_POT,atom2) = pot_col(VDW_POT,atom2) + 0.5_dp*pot_temp*sw
1157 gezelter 1608 #else
1158 chrisfen 1717 pot = pot + pot_temp*sw
1159 gezelter 1608 #endif
1160     endif
1161 chrisfen 1717
1162     !!$ write(*,*) 'drtdu, depsdu = ', drtduxi, depsduxi
1163 gezelter 2204
1164 gezelter 2756 dvdxi = 24.0_dp*eps*(2.0_dp*rt11 - rt5)*drtdxi + 4.0_dp*depsdxi*rt126
1165     dvdyi = 24.0_dp*eps*(2.0_dp*rt11 - rt5)*drtdyi + 4.0_dp*depsdyi*rt126
1166     dvdzi = 24.0_dp*eps*(2.0_dp*rt11 - rt5)*drtdzi + 4.0_dp*depsdzi*rt126
1167     dvduxi = 24.0_dp*eps*(2.0_dp*rt11 - rt5)*drtduxi + 4.0_dp*depsduxi*rt126
1168     dvduyi = 24.0_dp*eps*(2.0_dp*rt11 - rt5)*drtduyi + 4.0_dp*depsduyi*rt126
1169     dvduzi = 24.0_dp*eps*(2.0_dp*rt11 - rt5)*drtduzi + 4.0_dp*depsduzi*rt126
1170 gezelter 1608
1171 gezelter 2756 dvdxj = 24.0_dp*eps*(2.0_dp*rt11 - rt5)*drtdxj + 4.0_dp*depsdxj*rt126
1172     dvdyj = 24.0_dp*eps*(2.0_dp*rt11 - rt5)*drtdyj + 4.0_dp*depsdyj*rt126
1173     dvdzj = 24.0_dp*eps*(2.0_dp*rt11 - rt5)*drtdzj + 4.0_dp*depsdzj*rt126
1174     dvduxj = 24.0_dp*eps*(2.0_dp*rt11 - rt5)*drtduxj + 4.0_dp*depsduxj*rt126
1175     dvduyj = 24.0_dp*eps*(2.0_dp*rt11 - rt5)*drtduyj + 4.0_dp*depsduyj*rt126
1176     dvduzj = 24.0_dp*eps*(2.0_dp*rt11 - rt5)*drtduzj + 4.0_dp*depsduzj*rt126
1177 chrisfen 2214 !!$ write(*,*) 'drtduxi = ', drtduxi, ' depsduxi = ', depsduxi
1178 gezelter 1608 ! do the torques first since they are easy:
1179     ! remember that these are still in the body fixed axes
1180    
1181 gezelter 2756 txi = 0.0_dp
1182     tyi = 0.0_dp
1183     tzi = 0.0_dp
1184 gezelter 1707
1185 gezelter 2756 txj = 0.0_dp
1186     tyj = 0.0_dp
1187     tzj = 0.0_dp
1188 gezelter 1608
1189 chrisfen 2214 txi = (dvduyi - dvduzi) * sw
1190     tyi = (dvduzi - dvduxi) * sw
1191     tzi = (dvduxi - dvduyi) * sw
1192 gezelter 1608
1193 chrisfen 2214 txj = (dvduyj - dvduzj) * sw
1194     tyj = (dvduzj - dvduxj) * sw
1195     tzj = (dvduxj - dvduyj) * sw
1196 gezelter 2204
1197 chrisfen 2214 !!$ txi = dvduxi * sw
1198     !!$ tyi = dvduyi * sw
1199     !!$ tzi = dvduzi * sw
1200     !!$
1201     !!$ txj = dvduxj * sw
1202     !!$ tyj = dvduyj * sw
1203     !!$ tzj = dvduzj * sw
1204 chrisfen 2211
1205 chrisfen 1717 write(*,*) 't1 = ', txi, tyi, tzi
1206     write(*,*) 't2 = ', txj, tyj, tzj
1207    
1208 gezelter 1608 ! go back to lab frame using transpose of rotation matrix:
1209 gezelter 2204
1210 gezelter 1608 #ifdef IS_MPI
1211     t_Row(1,atom1) = t_Row(1,atom1) + a_Row(1,atom1)*txi + &
1212     a_Row(4,atom1)*tyi + a_Row(7,atom1)*tzi
1213     t_Row(2,atom1) = t_Row(2,atom1) + a_Row(2,atom1)*txi + &
1214     a_Row(5,atom1)*tyi + a_Row(8,atom1)*tzi
1215     t_Row(3,atom1) = t_Row(3,atom1) + a_Row(3,atom1)*txi + &
1216     a_Row(6,atom1)*tyi + a_Row(9,atom1)*tzi
1217 gezelter 2204
1218 gezelter 1608 t_Col(1,atom2) = t_Col(1,atom2) + a_Col(1,atom2)*txj + &
1219     a_Col(4,atom2)*tyj + a_Col(7,atom2)*tzj
1220     t_Col(2,atom2) = t_Col(2,atom2) + a_Col(2,atom2)*txj + &
1221 gezelter 2204 a_Col(5,atom2)*tyj + a_Col(8,atom2)*tzj
1222 gezelter 1608 t_Col(3,atom2) = t_Col(3,atom2) + a_Col(3,atom2)*txj + &
1223     a_Col(6,atom2)*tyj + a_Col(9,atom2)*tzj
1224     #else
1225     t(1,atom1) = t(1,atom1) + a(1,atom1)*txi + a(4,atom1)*tyi + a(7,atom1)*tzi
1226     t(2,atom1) = t(2,atom1) + a(2,atom1)*txi + a(5,atom1)*tyi + a(8,atom1)*tzi
1227     t(3,atom1) = t(3,atom1) + a(3,atom1)*txi + a(6,atom1)*tyi + a(9,atom1)*tzi
1228 gezelter 2204
1229 gezelter 1608 t(1,atom2) = t(1,atom2) + a(1,atom2)*txj + a(4,atom2)*tyj + a(7,atom2)*tzj
1230     t(2,atom2) = t(2,atom2) + a(2,atom2)*txj + a(5,atom2)*tyj + a(8,atom2)*tzj
1231     t(3,atom2) = t(3,atom2) + a(3,atom2)*txj + a(6,atom2)*tyj + a(9,atom2)*tzj
1232 chrisfen 2214
1233 gezelter 1608 #endif
1234     ! Now, on to the forces:
1235 gezelter 2204
1236 gezelter 1608 ! first rotate the i terms back into the lab frame:
1237 gezelter 2204
1238 chrisfen 2214 fxi = -dvdxi * sw
1239     fyi = -dvdyi * sw
1240     fzi = -dvdzi * sw
1241 gezelter 1608
1242 chrisfen 2214 fxj = -dvdxj * sw
1243     fyj = -dvdyj * sw
1244     fzj = -dvdzj * sw
1245 gezelter 1608
1246 chrisfen 2211
1247 gezelter 1608 #ifdef IS_MPI
1248     fxii = a_Row(1,atom1)*fxi + a_Row(4,atom1)*fyi + a_Row(7,atom1)*fzi
1249     fyii = a_Row(2,atom1)*fxi + a_Row(5,atom1)*fyi + a_Row(8,atom1)*fzi
1250     fzii = a_Row(3,atom1)*fxi + a_Row(6,atom1)*fyi + a_Row(9,atom1)*fzi
1251    
1252     fxjj = a_Col(1,atom2)*fxj + a_Col(4,atom2)*fyj + a_Col(7,atom2)*fzj
1253     fyjj = a_Col(2,atom2)*fxj + a_Col(5,atom2)*fyj + a_Col(8,atom2)*fzj
1254     fzjj = a_Col(3,atom2)*fxj + a_Col(6,atom2)*fyj + a_Col(9,atom2)*fzj
1255     #else
1256     fxii = a(1,atom1)*fxi + a(4,atom1)*fyi + a(7,atom1)*fzi
1257     fyii = a(2,atom1)*fxi + a(5,atom1)*fyi + a(8,atom1)*fzi
1258     fzii = a(3,atom1)*fxi + a(6,atom1)*fyi + a(9,atom1)*fzi
1259 gezelter 2204
1260 gezelter 1608 fxjj = a(1,atom2)*fxj + a(4,atom2)*fyj + a(7,atom2)*fzj
1261     fyjj = a(2,atom2)*fxj + a(5,atom2)*fyj + a(8,atom2)*fzj
1262     fzjj = a(3,atom2)*fxj + a(6,atom2)*fyj + a(9,atom2)*fzj
1263     #endif
1264    
1265     fxij = -fxii
1266     fyij = -fyii
1267     fzij = -fzii
1268 gezelter 2204
1269 gezelter 1608 fxji = -fxjj
1270     fyji = -fyjj
1271     fzji = -fzjj
1272    
1273 chrisfen 2214 fxradial = (fxii + fxji)
1274     fyradial = (fyii + fyji)
1275     fzradial = (fzii + fzji)
1276     !!$ write(*,*) fxradial, ' is fxrad; ', fyradial, ' is fyrad; ', fzradial, 'is fzrad'
1277 gezelter 1608 #ifdef IS_MPI
1278     f_Row(1,atom1) = f_Row(1,atom1) + fxradial
1279     f_Row(2,atom1) = f_Row(2,atom1) + fyradial
1280     f_Row(3,atom1) = f_Row(3,atom1) + fzradial
1281 gezelter 2204
1282 gezelter 1608 f_Col(1,atom2) = f_Col(1,atom2) - fxradial
1283     f_Col(2,atom2) = f_Col(2,atom2) - fyradial
1284     f_Col(3,atom2) = f_Col(3,atom2) - fzradial
1285     #else
1286     f(1,atom1) = f(1,atom1) + fxradial
1287     f(2,atom1) = f(2,atom1) + fyradial
1288     f(3,atom1) = f(3,atom1) + fzradial
1289 gezelter 2204
1290 gezelter 1608 f(1,atom2) = f(1,atom2) - fxradial
1291     f(2,atom2) = f(2,atom2) - fyradial
1292     f(3,atom2) = f(3,atom2) - fzradial
1293     #endif
1294    
1295     #ifdef IS_MPI
1296     id1 = AtomRowToGlobal(atom1)
1297     id2 = AtomColToGlobal(atom2)
1298     #else
1299     id1 = atom1
1300     id2 = atom2
1301     #endif
1302 gezelter 2204
1303 gezelter 1608 if (molMembershipList(id1) .ne. molMembershipList(id2)) then
1304 gezelter 2204
1305 gezelter 1608 fpair(1) = fpair(1) + fxradial
1306     fpair(2) = fpair(2) + fyradial
1307     fpair(3) = fpair(3) + fzradial
1308 gezelter 2204
1309 gezelter 1608 endif
1310 gezelter 1707
1311 gezelter 1608 end subroutine do_shape_pair
1312 gezelter 2204
1313 chrisfen 1689 SUBROUTINE Associated_Legendre(x, l, m, lmax, plm, dlm)
1314    
1315 gezelter 1608 ! Purpose: Compute the associated Legendre functions
1316     ! Plm(x) and their derivatives Plm'(x)
1317     ! Input : x --- Argument of Plm(x)
1318     ! l --- Order of Plm(x), l = 0,1,2,...,n
1319     ! m --- Degree of Plm(x), m = 0,1,2,...,N
1320     ! lmax --- Physical dimension of PLM and DLM
1321     ! Output: PLM(l,m) --- Plm(x)
1322     ! DLM(l,m) --- Plm'(x)
1323     !
1324     ! adapted from the routines in
1325     ! COMPUTATION OF SPECIAL FUNCTIONS by Shanjie Zhang and Jianming Jin
1326     ! ISBN 0-471-11963-6
1327     !
1328     ! The original Fortran77 codes can be found here:
1329     ! http://iris-lee3.ece.uiuc.edu/~jjin/routines/routines.html
1330 gezelter 2204
1331 chrisfen 1689 real (kind=dp), intent(in) :: x
1332 gezelter 1608 integer, intent(in) :: l, m, lmax
1333 chrisfen 1689 real (kind=dp), dimension(0:lmax,0:m), intent(out) :: PLM, DLM
1334 gezelter 1608 integer :: i, j, ls
1335 chrisfen 1689 real (kind=dp) :: xq, xs
1336 gezelter 1608
1337     ! zero out both arrays:
1338     DO I = 0, m
1339     DO J = 0, l
1340 chrisfen 1689 PLM(J,I) = 0.0_dp
1341     DLM(J,I) = 0.0_dp
1342 gezelter 1608 end DO
1343     end DO
1344    
1345     ! start with 0,0:
1346 gezelter 2756 PLM(0,0) = 1.0_DP
1347 gezelter 2204
1348 gezelter 1608 ! x = +/- 1 functions are easy:
1349 gezelter 2756 IF (abs(X).EQ.1.0_DP) THEN
1350 gezelter 1608 DO I = 1, m
1351     PLM(0, I) = X**I
1352 gezelter 2756 DLM(0, I) = 0.5_DP*I*(I+1.0_DP)*X**(I+1)
1353 gezelter 1608 end DO
1354     DO J = 1, m
1355     DO I = 1, l
1356     IF (I.EQ.1) THEN
1357     DLM(I, J) = 1.0D+300
1358     ELSE IF (I.EQ.2) THEN
1359 gezelter 2756 DLM(I, J) = -0.25_DP*(J+2)*(J+1)*J*(J-1)*X**(J+1)
1360 gezelter 1608 ENDIF
1361     end DO
1362     end DO
1363     RETURN
1364     ENDIF
1365    
1366     LS = 1
1367 gezelter 2756 IF (abs(X).GT.1.0_DP) LS = -1
1368     XQ = sqrt(LS*(1.0_DP-X*X))
1369     XS = LS*(1.0_DP-X*X)
1370 gezelter 1608
1371     DO I = 1, l
1372 gezelter 2756 PLM(I, I) = -LS*(2.0_DP*I-1.0_DP)*XQ*PLM(I-1, I-1)
1373 gezelter 1608 enddo
1374 chrisfen 1689
1375 gezelter 1608 DO I = 0, l
1376 gezelter 2756 PLM(I, I+1)=(2.0_DP*I+1.0_DP)*X*PLM(I, I)
1377 gezelter 1608 enddo
1378 chrisfen 1689
1379 gezelter 1608 DO I = 0, l
1380     DO J = I+2, m
1381 gezelter 2756 PLM(I, J)=((2.0_DP*J-1.0_DP)*X*PLM(I,J-1) - &
1382     (I+J-1.0_DP)*PLM(I,J-2))/(J-I)
1383 gezelter 1608 end DO
1384     end DO
1385 chrisfen 1689
1386 gezelter 2756 DLM(0, 0)=0.0_DP
1387 gezelter 1608 DO J = 1, m
1388     DLM(0, J)=LS*J*(PLM(0,J-1)-X*PLM(0,J))/XS
1389     end DO
1390 chrisfen 1689
1391 gezelter 1608 DO I = 1, l
1392     DO J = I, m
1393 gezelter 2756 DLM(I,J) = LS*I*X*PLM(I, J)/XS + (J+I)*(J-I+1.0_DP)/XQ*PLM(I-1, J)
1394 gezelter 1608 end DO
1395     end DO
1396 chrisfen 1689
1397 gezelter 1608 RETURN
1398     END SUBROUTINE Associated_Legendre
1399    
1400    
1401 chrisfen 1689 subroutine Orthogonal_Polynomial(x, m, mmax, function_type, pl, dpl)
1402 gezelter 2204
1403 gezelter 1608 ! Purpose: Compute orthogonal polynomials: Tn(x) or Un(x),
1404     ! or Ln(x) or Hn(x), and their derivatives
1405     ! Input : function_type --- Function code
1406     ! =1 for Chebyshev polynomial Tn(x)
1407     ! =2 for Chebyshev polynomial Un(x)
1408     ! =3 for Laguerre polynomial Ln(x)
1409     ! =4 for Hermite polynomial Hn(x)
1410     ! n --- Order of orthogonal polynomials
1411     ! x --- Argument of orthogonal polynomials
1412     ! Output: PL(n) --- Tn(x) or Un(x) or Ln(x) or Hn(x)
1413     ! DPL(n)--- Tn'(x) or Un'(x) or Ln'(x) or Hn'(x)
1414     !
1415     ! adapted from the routines in
1416     ! COMPUTATION OF SPECIAL FUNCTIONS by Shanjie Zhang and Jianming Jin
1417     ! ISBN 0-471-11963-6
1418     !
1419     ! The original Fortran77 codes can be found here:
1420     ! http://iris-lee3.ece.uiuc.edu/~jjin/routines/routines.html
1421 gezelter 2204
1422 gezelter 1608 real(kind=8), intent(in) :: x
1423 chrisfen 1689 integer, intent(in):: m, mmax
1424 gezelter 1608 integer, intent(in):: function_type
1425 chrisfen 1689 real(kind=8), dimension(0:mmax), intent(inout) :: pl, dpl
1426 gezelter 2204
1427 gezelter 1608 real(kind=8) :: a, b, c, y0, y1, dy0, dy1, yn, dyn
1428     integer :: k
1429    
1430 gezelter 2756 A = 2.0_DP
1431     B = 0.0_DP
1432     C = 1.0_DP
1433     Y0 = 1.0_DP
1434     Y1 = 2.0_DP*X
1435     DY0 = 0.0_DP
1436     DY1 = 2.0_DP
1437     PL(0) = 1.0_DP
1438     PL(1) = 2.0_DP*X
1439     DPL(0) = 0.0_DP
1440     DPL(1) = 2.0_DP
1441 gezelter 1608 IF (function_type.EQ.CHEBYSHEV_TN) THEN
1442     Y1 = X
1443 gezelter 2756 DY1 = 1.0_DP
1444 gezelter 1608 PL(1) = X
1445 gezelter 2756 DPL(1) = 1.0_DP
1446 gezelter 1608 ELSE IF (function_type.EQ.LAGUERRE) THEN
1447 gezelter 2756 Y1 = 1.0_DP-X
1448     DY1 = -1.0_DP
1449     PL(1) = 1.0_DP-X
1450     DPL(1) = -1.0_DP
1451 gezelter 1608 ENDIF
1452     DO K = 2, m
1453     IF (function_type.EQ.LAGUERRE) THEN
1454 gezelter 2756 A = -1.0_DP/K
1455     B = 2.0_DP+A
1456     C = 1.0_DP+A
1457 gezelter 1608 ELSE IF (function_type.EQ.HERMITE) THEN
1458 gezelter 2756 C = 2.0_DP*(K-1.0_DP)
1459 gezelter 1608 ENDIF
1460     YN = (A*X+B)*Y1-C*Y0
1461     DYN = A*Y1+(A*X+B)*DY1-C*DY0
1462     PL(K) = YN
1463     DPL(K) = DYN
1464     Y0 = Y1
1465     Y1 = YN
1466     DY0 = DY1
1467     DY1 = DYN
1468     end DO
1469 chrisfen 1698
1470    
1471 gezelter 1608 RETURN
1472 gezelter 2204
1473 gezelter 1608 end subroutine Orthogonal_Polynomial
1474 gezelter 2204
1475 chuckv 2188 subroutine deallocateShapes(this)
1476     type(Shape), pointer :: this
1477    
1478 gezelter 2204 if (associated( this%ContactFuncLValue)) then
1479     deallocate(this%ContactFuncLValue)
1480     this%ContactFuncLValue => null()
1481     end if
1482 chuckv 2188
1483 gezelter 2204 if (associated( this%ContactFuncMValue)) then
1484     deallocate( this%ContactFuncMValue)
1485     this%ContactFuncMValue => null()
1486     end if
1487     if (associated( this%ContactFunctionType)) then
1488     deallocate(this%ContactFunctionType)
1489     this%ContactFunctionType => null()
1490     end if
1491 chuckv 2188
1492 gezelter 2204 if (associated( this%ContactFuncCoefficient)) then
1493     deallocate(this%ContactFuncCoefficient)
1494     this%ContactFuncCoefficient => null()
1495     end if
1496 chuckv 2188
1497 gezelter 2204 if (associated( this%RangeFuncLValue)) then
1498     deallocate(this%RangeFuncLValue)
1499     this%RangeFuncLValue => null()
1500     end if
1501     if (associated( this%RangeFuncMValue)) then
1502     deallocate( this%RangeFuncMValue)
1503     this%RangeFuncMValue => null()
1504     end if
1505 chuckv 2188
1506 gezelter 2204 if (associated( this%RangeFunctionType)) then
1507     deallocate( this%RangeFunctionType)
1508     this%RangeFunctionType => null()
1509     end if
1510 chuckv 2188 if (associated( this%RangeFuncCoefficient)) then
1511     deallocate(this%RangeFuncCoefficient)
1512     this%RangeFuncCoefficient => null()
1513     end if
1514    
1515     if (associated( this%StrengthFuncLValue)) then
1516     deallocate(this%StrengthFuncLValue)
1517     this%StrengthFuncLValue => null()
1518     end if
1519    
1520     if (associated( this%StrengthFuncMValue )) then
1521     deallocate(this%StrengthFuncMValue)
1522     this%StrengthFuncMValue => null()
1523     end if
1524    
1525     if(associated( this%StrengthFunctionType)) then
1526     deallocate(this%StrengthFunctionType)
1527     this%StrengthFunctionType => null()
1528     end if
1529     if (associated( this%StrengthFuncCoefficient )) then
1530     deallocate(this%StrengthFuncCoefficient)
1531     this%StrengthFuncCoefficient => null()
1532     end if
1533     end subroutine deallocateShapes
1534    
1535     subroutine destroyShapeTypes
1536     integer :: i
1537     type(Shape), pointer :: thisShape
1538    
1539 gezelter 2204 ! First walk through and kill the shape
1540 chuckv 2188 do i = 1,ShapeMap%n_shapes
1541     thisShape => ShapeMap%Shapes(i)
1542     call deallocateShapes(thisShape)
1543     end do
1544 gezelter 2204
1545 chuckv 2188 ! set shape map to starting values
1546     ShapeMap%n_shapes = 0
1547     ShapeMap%currentShape = 0
1548 gezelter 2204
1549     if (associated(ShapeMap%Shapes)) then
1550 chuckv 2188 deallocate(ShapeMap%Shapes)
1551     ShapeMap%Shapes => null()
1552     end if
1553    
1554     if (associated(ShapeMap%atidToShape)) then
1555     deallocate(ShapeMap%atidToShape)
1556     ShapeMap%atidToShape => null()
1557     end if
1558    
1559    
1560     end subroutine destroyShapeTypes
1561    
1562 gezelter 2204
1563 gezelter 1608 end module shapes