ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/branches/new_design/OOPSE-4/src/UseTheForce/DarkSide/shapes.F90
Revision: 1683
Committed: Thu Oct 28 22:34:02 2004 UTC (19 years, 8 months ago)
File size: 47896 byte(s)
Log Message:
This commit was manufactured by cvs2svn to create branch 'new_design'.

File Contents

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