ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-4/src/UseTheForce/DarkSide/shapes.F90
Revision: 2277
Committed: Fri Aug 26 21:30:41 2005 UTC (19 years ago) by chrisfen
File size: 54178 byte(s)
Log Message:
added some probably nonfunctional get*cut routines

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