ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-4/src/UseTheForce/DarkSide/LJ.F90
(Generate patch)

Comparing trunk/OOPSE-4/src/UseTheForce/DarkSide/LJ.F90 (file contents):
Revision 2726 by gezelter, Thu Apr 20 18:24:24 2006 UTC vs.
Revision 2727 by chrisfen, Fri Apr 21 19:32:07 2006 UTC

# Line 43 | Line 43
43   !! Calculates Long Range forces Lennard-Jones interactions.
44   !! @author Charles F. Vardeman II
45   !! @author Matthew Meineke
46 < !! @version $Id: LJ.F90,v 1.22 2006-04-20 18:24:24 gezelter Exp $, $Date: 2006-04-20 18:24:24 $, $Name: not supported by cvs2svn $, $Revision: 1.22 $
46 > !! @version $Id: LJ.F90,v 1.23 2006-04-21 19:32:07 chrisfen Exp $, $Date: 2006-04-21 19:32:07 $, $Name: not supported by cvs2svn $, $Revision: 1.23 $
47  
48  
49   module lj
# Line 52 | Line 52 | module lj
52    use simulation
53    use status
54    use fForceOptions
55  use interpolation
55   #ifdef IS_MPI
56    use mpiSimulation
57   #endif
# Line 67 | Line 66 | module lj
66  
67    logical, save :: useGeometricDistanceMixing = .false.
68    logical, save :: haveMixingMap = .false.
70  logical, save :: useSplines = .false.
69  
70    real(kind=DP), save :: defaultCutoff = 0.0_DP
71    logical, save :: defaultShift = .false.
# Line 101 | Line 99 | module lj
99  
100    type(MixParameters), dimension(:,:), allocatable :: MixingMap
101  
104  type(cubicSpline), save :: vLJspline
105  type(cubicSpline), save :: vLJpspline
106  type(cubicSpline), save :: vSoftSpline
107  type(cubicSpline), save :: vSoftpSpline
108
102    public :: newLJtype
103    public :: setLJDefaultCutoff
104    public :: getSigma
105    public :: getEpsilon
106    public :: do_lj_pair
107    public :: destroyLJtypes
115  public :: setLJsplineRmax
108  
109   contains
110  
# Line 163 | Line 155 | contains
155      defaultCutoff = thisRcut
156      defaultShift = shiftedPot
157      haveDefaultCutoff = .true.
158 <    !we only want to build LJ Mixing map and spline if LJ is being used.
158 >    !we only want to build LJ Mixing map if LJ is being used.
159      if(LJMap%nLJTypes /= 0) then
160         call createMixingMap()
169       call setLJsplineRmax(defaultCutoff)
161      end if
162  
163    end subroutine setLJDefaultCutoff
# Line 266 | Line 257 | contains
257      haveMixingMap = .true.
258      
259    end subroutine createMixingMap
260 <  
270 <  subroutine setLJsplineRmax(largestRcut)
271 <    real( kind = dp ), intent(in) :: largestRcut
272 <    real( kind = dp ) :: s, bigS, smallS, rmax, rmin
273 <    integer :: np, i
274 <
275 <    if (LJMap%nLJtypes .ne. 0) then
276 <
277 <       !
278 <       ! find the largest and smallest values of sigma that we'll need
279 <       !
280 <       bigS = 0.0_DP
281 <       smallS = 1.0e9
282 <       do i = 1, LJMap%nLJtypes
283 <          s = LJMap%LJtypes(i)%sigma
284 <          if (s .gt. bigS) bigS = s
285 <          if (s .lt. smallS) smallS = s
286 <       enddo
287 <      
288 <       !
289 <       ! give ourselves a 20% margin just in case
290 <       !
291 <       rmax = 1.2 * largestRcut / smallS    
292 <       !
293 <       ! assume atoms will never get closer than 1 angstrom
294 <       !
295 <       rmin = 1 / bigS
296 <       !
297 <       ! assume 500 points is enough
298 <       !
299 <       np = 500
300 <      
301 <       write(*,*) 'calling setupSplines with rmin = ', rmin, ' rmax = ', rmax, &
302 <            ' np = ', np
303 <      
304 <       call setupSplines(rmin, rmax, np)
305 <
306 <    endif
307 <    return
308 <  end subroutine setLJsplineRmax
309 <        
260 >          
261    subroutine do_lj_pair(atom1, atom2, d, rij, r2, rcut, sw, vpair, fpair, &
262         pot, f, do_pot)
263      
# Line 450 | Line 401 | contains
401      
402      haveMixingMap = .false.
403  
453    call deleteSpline(vLJspline)
454    call deleteSpline(vLJpspline)
455    call deleteSpline(vSoftSpline)
456    call deleteSpline(vSoftpSpline)
457
404    end subroutine destroyLJTypes
405  
406    subroutine getLJfunc(r, myPot, myDeriv)
# Line 465 | Line 411 | contains
411      real(kind=dp) :: a, b, c, d, dx
412      integer :: j
413  
414 <    if (useSplines) then
415 <
416 <       call lookupUniformSpline1d(vLJSpline, r, myPot, myDeriv)
417 <      
418 <    else
419 <       ri = 1.0_DP / r
420 <       ri2 = ri*ri
421 <       ri6 = ri2*ri2*ri2
422 <       ri7 = ri6*ri
423 <       ri12 = ri6*ri6
478 <       ri13 = ri12*ri
479 <      
480 <       myPot = 4.0_DP * (ri12 - ri6)
481 <       myDeriv = 24.0_DP * (ri7 - 2.0_DP * ri13)
482 <    endif
483 <
414 >    ri = 1.0_DP / r
415 >    ri2 = ri*ri
416 >    ri6 = ri2*ri2*ri2
417 >    ri7 = ri6*ri
418 >    ri12 = ri6*ri6
419 >    ri13 = ri12*ri
420 >    
421 >    myPot = 4.0_DP * (ri12 - ri6)
422 >    myDeriv = 24.0_DP * (ri7 - 2.0_DP * ri13)
423 >    
424      return
425    end subroutine getLJfunc
426  
# Line 492 | Line 432 | contains
432      real(kind=dp) :: a, b, c, d, dx
433      integer :: j
434      
435 <    if (useSplines) then
436 <
437 <       call lookupUniformSpline1d(vSoftSpline, r, myPot, myDeriv)
438 <      
439 <    else
440 <       ri = 1.0_DP / r    
441 <       ri2 = ri*ri
502 <       ri6 = ri2*ri2*ri2
503 <       ri7 = ri6*ri
504 <       myPot = 4.0_DP * (ri6)
505 <       myDeriv = - 24.0_DP * ri7
506 <    endif
507 <
435 >    ri = 1.0_DP / r    
436 >    ri2 = ri*ri
437 >    ri6 = ri2*ri2*ri2
438 >    ri7 = ri6*ri
439 >    myPot = 4.0_DP * (ri6)
440 >    myDeriv = - 24.0_DP * ri7
441 >    
442      return
443    end subroutine getSoftFunc
444  
511  subroutine setupSplines(rmin, rmax, np)
512    real( kind = dp ), intent(in) :: rmin, rmax
513    integer, intent(in) :: np
514    real( kind = dp ) :: rvals(np), vLJ(np), vLJp(np), vSoft(np), vSoftp(np)
515    real( kind = dp ) :: dr, r, ri, ri2, ri6, ri7, ri12, ri13
516    integer :: i
517
518    dr = (rmax-rmin) / float(np-1)
519    
520    do i = 1, np
521       r = rmin + dble(i-1)*dr
522       ri = 1.0_DP / r
523       ri2 = ri*ri
524       ri6 = ri2*ri2*ri2
525       ri7 = ri6*ri
526       ri12 = ri6*ri6
527       ri13 = ri12*ri
528
529       rvals(i) = r
530       vLJ(i) = 4.0_DP * (ri12 - ri6)
531       vLJp(i) = 24.0_DP * (ri7 - 2.0_DP * ri13)
532
533       vSoft(i) = 4.0_DP * (ri6)
534       vSoftp(i) = - 24.0_DP * ri7      
535    enddo
536
537    call newSpline(vLJspline, rvals, vLJ,  .true.)
538    call newSpline(vLJpspline, rvals, vLJp, .true.)
539    call newSpline(vSoftSpline, rvals, vSoft,  .true.)
540    call newSpline(vSoftpSpline, rvals, vSoftp, .true.)
541
542    return
543  end subroutine setupSplines
445   end module lj

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines